diff --git a/grease/Core/Collections/GROrderedMultiMap.st b/grease/Core/Collections/GROrderedMultiMap.st deleted file mode 100644 index 68d86fe..0000000 --- a/grease/Core/Collections/GROrderedMultiMap.st +++ /dev/null @@ -1,48 +0,0 @@ -GRSmallDictionary subclass: GROrderedMultiMap [ - - - - - add: anAssociation [ - - self privateAt: anAssociation key put: anAssociation value. - ^anAssociation - ] - - allAt: aKey [ - - ^Array streamContents: [:stream | - 1 to: size do: [:index | - (keys at: index) = aKey ifTrue: [ - stream nextPut: (values at: index)]]] - ] - - allAt: aKey ifAbsent: absentBlock [ - - | results | - results := self allAt: aKey. - ^results isEmpty ifTrue: [absentBlock value] ifFalse: [results] - ] - - at: aKey add: aValue [ - "Add an association between aKey and aValue. Do not replace existing - values with the same key." - - - ^self privateAt: aKey put: aValue - ] - - removeKey: aKey ifAbsent: aBlock [ - "Remove aKey from the receiver, evaluate aBlock if the element is missing." - - "This is inefficient and could be optimized." - - - | removed | - removed := Array streamContents: [:stream | | index | - [(index := self findIndexFor: aKey) = 0] - whileFalse: [stream nextPut: (self removeIndex: index)]]. - ^removed isEmpty ifTrue: [aBlock value] ifFalse: [removed] - ] -] - diff --git a/grease/Core/Collections/GRSmallDictionary.st b/grease/Core/Collections/GRSmallDictionary.st deleted file mode 100644 index ff26f4a..0000000 --- a/grease/Core/Collections/GRSmallDictionary.st +++ /dev/null @@ -1,244 +0,0 @@ -GRObject subclass: GRSmallDictionary [ - | size keys values | - - - - - GRSmallDictionary class [ - - new [ - - ^self new: 3 - ] - - new: anInteger [ - - ^self basicNew initialize: anInteger - ] - - withAll: aCollection [ - - ^self new addAll: aCollection; yourself - ] -] - - initialize: anInteger [ - - size := 0. - keys := Array new: anInteger. - values := Array new: anInteger - ] - - isEmpty [ - - ^size = 0 - ] - - isDictionary [ - - ^true - ] - - isCollection [ - - ^true - ] - - add: anAssociation [ - - self at: anAssociation key put: anAssociation value. - ^anAssociation - ] - - addAll: aDictionary [ - - aDictionary keysAndValuesDo: [ :key :value | self add: key -> value ]. - ^aDictionary - ] - - at: aKey [ - "Answer the value associated with aKey. Raise an exception, if no such key is defined." - - - ^self at: aKey ifAbsent: [self errorKeyNotFound] - ] - - at: aKey ifAbsent: aBlock [ - "Answer the value associated with aKey. Evaluate aBlock, if no such key is defined." - - - | index | - index := self findIndexFor: aKey. - ^index = 0 ifFalse: [values at: index] ifTrue: [aBlock value] - ] - - at: aKey ifAbsentPut: aBlock [ - "Answer the value associated with aKey. Evaluate aBlock, if no such key is defined and store the return value." - - - | index | - index := self findIndexFor: aKey. - ^index = 0 - ifFalse: [values at: index] - ifTrue: [self privateAt: aKey put: aBlock value] - ] - - at: aKey ifPresent: aBlock [ - "Lookup aKey in the receiver. If it is present, answer the value of evaluating the given block with the value associated with the key. Otherwise, answer nil." - - - | index | - index := self findIndexFor: aKey. - ^index = 0 ifFalse: [aBlock value: (values at: index)] - ] - - at: aKey put: aValue [ - "Set the value of aKey to be aValue." - - - | index | - index := self findIndexFor: aKey. - ^index = 0 - ifFalse: [values at: index put: aValue] - ifTrue: [self privateAt: aKey put: aValue] - ] - - includesKey: aKey [ - "Answer whether the receiver has a key equal to aKey." - - - ^(self findIndexFor: aKey) ~= 0 - ] - - keys [ - - ^keys copyFrom: 1 to: size - ] - - associations [ - "Answer a Collection containing the receiver's associations." - - - | result | - result := WriteStream on: (Array new: self size). - self associationsDo: [:assoc | result nextPut: assoc]. - ^result contents - ] - - associationsDo: aBlock [ - - self keysAndValuesDo: [:key :value | aBlock value: key -> value] - ] - - do: aBlock [ - - 1 to: size do: [ :index | aBlock value: (values at: index) ] - ] - - keysAndValuesDo: aBlock [ - - 1 to: size - do: [:index | aBlock value: (keys at: index) value: (values at: index)] - ] - - postCopy [ - - super postCopy. - keys := keys copy. - values := values copy - ] - - size [ - - ^size - ] - - grow [ - - | newKeys newValues | - newKeys := Array new: 2 * size. - newValues := Array new: 2 * size. - 1 to: size - do: - [:index | - newKeys at: index put: (keys at: index). - newValues at: index put: (values at: index)]. - keys := newKeys. - values := newValues - ] - - errorKeyNotFound [ - - self error: 'Key not found' - ] - - findIndexFor: aKey [ - - 1 to: size do: [:index | (keys at: index) = aKey ifTrue: [^index]]. - ^0 - ] - - removeIndex: index [ - - | value | - value := values at: index. - index to: size - 1 do: - [ :i | - keys at: i put: (keys at: i + 1). - values at: i put: (values at: i + 1) ]. - keys at: size put: nil. - values at: size put: nil. - size := size - 1. - ^ value - ] - - privateAt: aKey put: aValue [ - - size = keys size ifTrue: [self grow]. - keys at: (size := size + 1) put: aKey. - ^values at: size put: aValue - ] - - values [ - - ^values copyFrom: 1 to: size - ] - - valuesDo: aBlock [ - - 1 to: size do: [:index | aBlock value: (values at: index)] - ] - - removeKey: aKey [ - "Remove aKey from the receiver, raise an exception if the element is missing." - - - ^self removeKey: aKey ifAbsent: [self errorKeyNotFound] - ] - - keysDo: aBlock [ - - 1 to: size do: [:each | aBlock value: (keys at: each)] - ] - - removeKey: aKey ifAbsent: aBlock [ - "Remove aKey from the receiver, evaluate aBlock if the element is missing." - - - | index value | - index := self findIndexFor: aKey. - index = 0 ifTrue: [^aBlock value]. - value := values at: index. - index to: size - 1 - do: - [:i | - keys at: i put: (keys at: i + 1). - values at: i put: (values at: i + 1)]. - keys at: size put: nil. - values at: size put: nil. - size := size - 1. - ^value - ] - -] - diff --git a/grease/Core/Exceptions.st b/grease/Core/Exceptions.st deleted file mode 100644 index aca48a2..0000000 --- a/grease/Core/Exceptions.st +++ /dev/null @@ -1,53 +0,0 @@ -Error subclass: GRError [ - - - - - GRError class >> new [ - - ^super new initialize - ] - - initialize [ - - ] -] - -Notification subclass: GRNotification [ - - - - - GRNotification class >> new [ - - ^super new initialize - ] - - initialize [ - - ] - -] - -GRNotification subclass: GRDeprecatedApiNotification [ - | details | - - - >#seasideDeprecatedApi:details: '> - - details [ - - ^details - ] - - details: anObject [ - - details := anObject - ] -] diff --git a/grease/Core/Extensions.st b/grease/Core/Extensions.st deleted file mode 100644 index fa14863..0000000 --- a/grease/Core/Extensions.st +++ /dev/null @@ -1,222 +0,0 @@ -Object extend [ - - greaseDeprecatedApi: apiString details: detailsString [ - - Grease.GRDeprecatedApiNotification new - details: detailsString; - signal: apiString - ] - - isCollection [ - - ^false - ] - - greaseString [ - - ^self printString - ] -] - -String extend [ - - greaseString [ - - ^self - ] - - excerpt: aString [ - - "Answer an excerpt of the receiver that matches the first occurence of aString. If aString isn't found, nil is answered." - - ^self excerpt: aString radius: 100 - ] - - excerpt: aString radius: anInteger [ - - "Answer an excerpt of the receiver that matches the first occurence of aString. - The radius anInteger expands the excerpt on each side of the first occurrence by the number of characters defined in radius. - If aString isn't found, nil is answered." - - ^self excerpt: aString radius: anInteger ellipsis: '...' - ] - - excerpt: aString radius: anInteger ellipsis: anEllipsisString [ - - "Answer an excerpt of the receiver that matches the first occurence of aString. - The radius anInteger expands the excerpt on each side of the first occurrence by the number of characters defined in radius. - If aString isn't found, nil is answered." - - | index start stop | - (aString isEmpty or: [ (index := self indexOfSubCollection: aString) = 0 ]) - ifTrue: [ ^ nil ]. - start := index - anInteger max: 1. - stop := index + anInteger + aString size - 1 min: self size. - ^(start > 1 ifTrue: [ anEllipsisString ] ifFalse: [ '' ]) , - (self copyFrom: start to: stop) , - (stop < self size ifTrue: [ anEllipsisString ] ifFalse: [ '' ]) - ] - - greaseInteger [ - - "Convert the receiver to an integer, answer nil if this is not a number." - - | number stream negated char | - number := nil. - stream := self readStream. - negated := stream peek = $-. - negated ifTrue: [ stream next ]. - [ stream atEnd not and: [ (char := stream next) isDigit ] ] whileTrue: - [ number := (number isNil - ifTrue: [ 0 ] - ifFalse: [ 10 * number ]) + (char greaseInteger - $0 greaseInteger) ]. - ^(number isNil or: [ negated not ]) - ifFalse: [ number negated ] - ifTrue: [ number ] - ] - - pluralize [ - - ^ Grease.GRInflector pluralize: self - ] - - print: anObject on: aStream [ - - aStream nextPutAll: self - ] - - trimBoth [ - - "Trim separators from both sides of the receiving string." - - ^ self trimBoth: [ :char | char isSeparator ] - ] - - trimBoth: aBlock [ - - "Trim characters satisfying the condition given in aBlock from both sides of the receiving string." - - ^ self trimLeft: aBlock right: aBlock - ] - - trimLeft [ - - "Trim separators from the left side of the receiving string." - - ^ self trimLeft: [ :char | char isSeparator ] - ] - - trimLeft: aBlock [ - - "Trim characters satisfying the condition given in aBlock from the left side of the receiving string." - - ^ self trimLeft: aBlock right: [ :char | false ] - ] - - trimLeft: aLeftBlock right: aRightBlock [ - - "Trim characters satisfying the condition given in aLeftBlock from the left side and aRightBlock from the right sides of the receiving string." - - | left right | - left := 1. - right := self size. - [ left <= right and: [ aLeftBlock value: (self at: left) ] ] - whileTrue: [ left := left + 1 ]. - [ left <= right and: [ aRightBlock value: (self at: right) ] ] - whileTrue: [ right := right - 1 ]. - ^ self copyFrom: left to: right - ] - - trimRight [ - - "Trim separators from the right side of the receiving string." - - ^ self trimRight: [ :char | char isSeparator ] - ] - - trimRight: aBlock [ - - "Trim characters satisfying the condition given in aBlock from the right side of the receiving string." - - ^ self trimLeft: [ :char | false ] right: aBlock - ] - - truncate [ - - "Truncate the receiver to 30 characters." - - ^ self truncate: 30 - ] - - truncate: anInteger [ - - "Truncate the receiver to anInteger characters." - - ^ self truncate: anInteger ellipsis: '...' - ] - - truncate: anInteger ellipsis: aString [ - - "Truncate the receiver to anInteger characters and append aString as ellipsis if necessary." - - ^ anInteger < self size - ifTrue: [ (self copyFrom: 1 to: anInteger) , aString ] - ifFalse: [ self copy ] - ] -] - -Symbol extend [ - - greaseString [ - - ^self asString - ] -] - -Number extend [ - - greaseInteger [ - - "Answer an integer of the receiver, in our case we simply truncate the number." - ^ self truncated - ] -] - -Integer extend [ - - greaseInteger [ - - ^ self - ] - - pluralize: aSingularString [ - - ^ self - pluralize: aSingularString - with: (Grease.GRInflector pluralize: aSingularString) - ] - - pluralize: aSingularString with: aPluralString [ - - ^ self printString , ' ' , (self abs = 1 ifTrue: [ aSingularString ] ifFalse: [ aPluralString ]) - ] -] - -Character extend [ - - print: anObject on: aStream [ - - aStream nextPut: self - ] - - greaseString [ - - ^self asString - ] -] - -UndefinedObject extend [ - print: anObject on: aStream [ - - ] -] diff --git a/grease/Core/GRObject.st b/grease/Core/GRObject.st deleted file mode 100644 index 0900d49..0000000 --- a/grease/Core/GRObject.st +++ /dev/null @@ -1,32 +0,0 @@ -Object subclass: GRObject [ - - - - - GRObject class >> defaultErrorClass [ - - ^GRError - ] - - GRObject class >> error: aString [ - - ^self defaultErrorClass signal: aString - ] - - GRObject class >> new [ - - ^self basicNew initialize - ] - - error: aString [ - - ^self class error: aString - ] - - initialize [ - - - ] -] - diff --git a/grease/Core/GRPackage.st b/grease/Core/GRPackage.st deleted file mode 100644 index a70c1ff..0000000 --- a/grease/Core/GRPackage.st +++ /dev/null @@ -1,168 +0,0 @@ -GRObject subclass: GRPackage [ - | name description dependencies license url | - - - - - - GRPackage class >> greaseTestsCore [ - - ^(self new) - name: 'Grease-Tests-Core'; - description: 'Unit tests for the package Grease-Core.'; - addDependency: 'Grease-Core'; - url: #seasideUrl; - yourself - ] - - GRPackage class >> greaseCore [ - - ^(self new) - name: 'Grease-Core'; - description: 'The main package of the Grease compatibility layer.'; - url: #seasideUrl; - yourself - ] - - GRPackage class >> packages [ - "Answer a list of all registered packages. - A package is registered by adding a class extension to the receiving class answering an instance of the receiving class." - - - | packages package | - packages := Dictionary new. - self class selectors do: - [:each | - (each numArgs = 0 and: [each ~= #packages]) - ifTrue: - [package := self perform: each. - packages at: package name put: package]]. - packages do: [:each | each resolveWith: packages]. - ^packages values - ] - - initialize [ - - super initialize. - dependencies := OrderedCollection new. - license := #MIT - ] - - description [ - "Answer a short description of the package." - - - ^description - ] - - description: aString [ - - description := aString - ] - - license [ - "Answer the current license of this package, by default MIT is used." - - - ^license - ] - - license: aSymbol [ - - license := aSymbol - ] - - name [ - "Answer the name of the package. This string should be useable to identify the platform specific native package object, e.g. the Monticello package name." - - - ^name - ] - - name: aString [ - - name := aString - ] - - url [ - "Answer the base-URL of the package. This string is only meaningful for platforms that can directly access Monticello repositories." - - - ^url isSymbol ifTrue: [self perform: url] ifFalse: [url] - ] - - url: aStringOrSymbol [ - "Set the base-URL of the package, or a symbol referring to a method in this class that answers the URL. This setting is only meaningful for platforms that can directly access Monticello repositories." - - - url := aStringOrSymbol - ] - - addDependency: aString [ - - dependencies add: aString - ] - - allDependencies [ - "Answer all dependencies on which this package depends." - - - ^self addDependenciesTo: OrderedCollection new - ] - - dependencies [ - "Return a collection of package names on which this package depends." - - - ^dependencies - ] - - resolveWith: aDictionary [ - - dependencies := dependencies collect: - [:each | - aDictionary at: each - ifAbsent: - [self error: self name printString , ' depends on unknown package ' - , each printString]] - ] - - printOn: aStream [ - - super printOn: aStream. - aStream - nextPut: $(; - nextPutAll: self name; - nextPut: $) - ] - - isLGPL [ - - ^self license = #LGPL - ] - - isMIT [ - - ^self license = #MIT - ] - - addDependenciesTo: aCollection [ - - (aCollection includes: self) - ifFalse: - [self dependencies do: [:each | each addDependenciesTo: aCollection]. - aCollection add: self]. - ^aCollection - ] - - seasideLGPLUrl [ - - ^'http://www.squeaksource.com/Seaside30LGPL' - ] - - seasideUrl [ - - ^'http://www.squeaksource.com/Seaside30' - ] -] - diff --git a/grease/Core/GRPlatform.st b/grease/Core/GRPlatform.st deleted file mode 100644 index 00d0ede..0000000 --- a/grease/Core/GRPlatform.st +++ /dev/null @@ -1,259 +0,0 @@ -GRObject subclass: GRPlatform [ - - - - - - Current := nil. - - GRPlatform class >> current [ - - ^Current - ] - - GRPlatform class >> current: aPlatform [ - - Current := aPlatform - ] - - GRPlatform class >> select [ - - GRPlatform current: self new - ] - - GRPlatform class >> unselect [ - - GRPlatform current class = self ifTrue: [GRPlatform current: nil] - ] - - secureHashFor: aString [ - - self subclassResponsibility - ] - - base64Decode: aString [ - - self subclassResponsibility - ] - - openDebuggerOn: anError [ - - self subclassResponsibility - ] - - stackDepth [ - - self subclassResponsibility - ] - - newRandom [ - "Answers the random number generator to be used to create session and continuation keys. Make sure it is seeded. The only methods that will be sent to it are: - #nextInt: - should answer a random integer in the interval [1, anInteger] - #randomFrom: - should answer a random element from the given collection - - Make sure that both methods are safe under heavy concurrent load. - - Used by Gemstone/S traditional Randoms which cannot be persisted. - Used by Squeak to use a secure random when avaiable." - - - self subclassResponsibility - ] - - readWriteByteStream [ - "Return a ReadWriteStream on a ByteArray that stores integers 0..255 - ^ReadWriteStream on: ByteArray new - " - - - ^self subclassResponsibility - ] - - readWriteCharacterStream [ - "Return a ReadWriteStream on a String that stores characters - ^ReadWriteStream on: String new - " - - - ^self subclassResponsibility - ] - - reducedConflictDictionary [ - "used by Gemstone/S reduced conflict classes that can be used to avoid transaction conflicts" - - - ^Dictionary - ] - - semaphoreClass [ - "used by Gemstone/S traditional Semaphores which cannot be persisted" - - - self subclassResponsibility - ] - - weakDictionaryOfSize: aNumber [ - - self subclassResponsibility - ] - - asMethodReturningByteArray: aByteArrayOrString named: aSymbol [ - "Generates the source of a method named aSymbol that returns aByteArrayOrString as a ByteArray" - - - self subclassResponsibility - ] - - compile: aString into: aClass classified: aSymbol [ - "The trick here is to be as silently a possible so that the package is not marked dirty when running WAFileLibrary test. - This also makes running tests much faster." - - - self subclassResponsibility - ] - - contentsOfFile: aString binary: aBoolean [ - - self subclassResponsibility - ] - - convertToSmalltalkNewlines: aString [ - "convert any line endings (CR, CRLF, LF) to CR" - - - self subclassResponsibility - ] - - ensureExistenceOfFolder: aString [ - "creates a folder named aString in the image directory" - - - self subclassResponsibility - ] - - filesIn: aPathString [ - "Return a collection of absolute paths for all the files (no directories) in the directory given by aPathString - must not include file names that start with ." - - - self subclassResponsibility - ] - - localNameOf: aFilename [ - "Answers the local name of a file indentified by an absolute file path. - - Eg. - If the platform is Windwos and aFilename is 'C:\Windows\win32.dll' then it would answer 'win32.dll'. - If the platform is Unix and aFilename is '/usr/bin/vim' then it would answer 'vim'." - - - self subclassResponsibility - ] - - removeSelector: aSymbol from: aClass [ - - self subclassResponsibility - ] - - write: aStringOrByteArray toFile: aFileNameString inFolder: aFolderString [ - "writes aStringOrByteArray to a file named aFilenameString in the folder aFolderString" - - - self subclassResponsibility - ] - - isProcessTerminated: aProcess [ - "Return a boolean indicating whether aProcess has been terminated." - - - self subclassResponsibility - ] - - terminateProcess: aProcess [ - "Permanently terminate the process, unwinding first to execute #ensure: and #ifCurtailed: blocks." - - - self subclassResponsibility - ] - - addToShutDownList: anObject [ - "Add anObject to the shutdown-list of the system. On shutdown the message #shutDown will be sent to anObject." - - - self subclassResponsibility - ] - - addToStartUpList: anObject [ - "Add anObject to the startup-list of the system. On startup the message #startUp will be sent to anObject." - - - self subclassResponsibility - ] - - removeFromShutDownList: anObject [ - "Remove anObject from the shutdown list in the system." - - - self subclassResponsibility - ] - - removeFromStartUpList: anObject [ - "Remove anObject from the startup list in the system." - - - self subclassResponsibility - ] - - newline [ - "Answer the system's default newline character (sequence)." - - - self subclsasResponsibility - ] - - doTransaction: aBlock [ - "for Gemstone/S compatibility - http://gemstonesoup.wordpress.com/2007/05/10/porting-application-specific-seaside-threads-to-gemstone/ - use when modifying an object from an outside thread" - - - ^aBlock value - ] - - label [ - "Answer a descriptive label string for the platform implementation" - - - self subclassResponsibility - ] - - version [ - "Answer the Grease version" - - - ^(GRVersion major: 1 minor: 0) - beAlpha: 6; - yourself - ] - - versionString [ - - ^String streamContents: - [:stream | - stream - nextPutAll: self version greaseString; - nextPutAll: ' ('; - nextPutAll: self label; - nextPut: $)] - ] -] - diff --git a/grease/Core/GRVersion.st b/grease/Core/GRVersion.st deleted file mode 100644 index 21723e5..0000000 --- a/grease/Core/GRVersion.st +++ /dev/null @@ -1,190 +0,0 @@ -GRObject subclass: GRVersion [ - | major minor revision stageLabel stageNumber | - - - - - GRVersion class >> major: majorInteger [ - - ^self major: majorInteger minor: nil - ] - - GRVersion class >> major: majorInteger minor: minorInteger [ - - ^self - major: majorInteger - minor: minorInteger - revision: nil - ] - - GRVersion class >> major: majorInteger minor: minorInteger revision: revisionInteger [ - - ^(self basicNew) - initializeWithMajor: majorInteger - minor: minorInteger - revision: revisionInteger; - yourself - ] - - GRVersion class >> new [ - - ^self major: 1 - ] - - initializeWithMajor: majorInteger minor: minorInteger revision: revisionInteger [ - - self initialize. - major := majorInteger. - minor := minorInteger. - revision := revisionInteger - ] - - < otherVersion [ - - major < otherVersion major ifTrue: [^true]. - otherVersion major < major ifTrue: [^false]. - (minor ifNil: [0]) < (otherVersion minor ifNil: [0]) ifTrue: [^true]. - (otherVersion minor ifNil: [0]) < (minor ifNil: [0]) ifTrue: [^false]. - (revision ifNil: [0]) < (otherVersion revision ifNil: [0]) ifTrue: [^true]. - (otherVersion revision ifNil: [0]) < (revision ifNil: [0]) - ifTrue: [^false]. - stageLabel = otherVersion stage - ifTrue: [^(stageNumber ifNil: [1]) < (otherVersion stageNumber ifNil: [1])]. - stageLabel isNil ifTrue: [^false]. - otherVersion stage isNil ifTrue: [^true]. - ^stageLabel < otherVersion stage - ] - - <= otherVersion [ - - ^(self > otherVersion) not - ] - - = otherVersion [ - - ^major = otherVersion major and: - [(minor ifNil: [0]) = (otherVersion minor ifNil: [0]) and: - [(revision ifNil: [0]) = (otherVersion revision ifNil: [0]) and: - [stageLabel = otherVersion stage - and: [(stageNumber ifNil: [1]) = (otherVersion stageNumber ifNil: [1])]]]] - ] - - > otherVersion [ - - ^otherVersion < self - ] - - >= otherVersion [ - - ^(self < otherVersion) not - ] - - hash [ - - ^(major hash bitXor: minor hash) bitXor: revision hash - ] - - beAlpha [ - - self beAlpha: nil - ] - - beAlpha: anInteger [ - - self stage: #alpha number: anInteger - ] - - beBeta [ - - self beBeta: nil - ] - - beBeta: anInteger [ - - self stage: #beta number: anInteger - ] - - beFinal [ - - self stage: nil number: nil - ] - - greaseString [ - - ^String streamContents: - [:stream | - stream nextPutAll: major greaseString. - stream nextPut: $.. - stream nextPutAll: (minor ifNil: [0]) greaseString. - revision isNil - ifFalse: - [stream nextPut: $.. - stream nextPutAll: revision greaseString]. - stageLabel isNil - ifFalse: - [stream nextPutAll: stageLabel greaseString. - stageNumber isNil ifFalse: [stream nextPutAll: stageNumber greaseString]]] - ] - - isAlpha [ - - ^stageLabel = #alpha - ] - - isBeta [ - - ^stageLabel = #beta - ] - - isFinal [ - - ^stageLabel isNil - ] - - major [ - - ^major - ] - - major: anInteger [ - - major := anInteger - ] - - minor [ - - ^minor - ] - - minor: anInteger [ - - minor := anInteger - ] - - revision [ - - ^revision - ] - - revision: anInteger [ - - revision := anInteger - ] - - stage [ - - ^stageLabel - ] - - stage: aSymbol number: anInteger [ - - stageLabel := aSymbol. - stageNumber := anInteger - ] - - stageNumber [ - - ^stageNumber - ] -] - diff --git a/grease/Core/Text/GRCodec.st b/grease/Core/Text/GRCodec.st deleted file mode 100644 index ec31c19..0000000 --- a/grease/Core/Text/GRCodec.st +++ /dev/null @@ -1,107 +0,0 @@ -GRObject subclass: GRCodec [ - - - - - GRCodec class >> allCodecs [ - "Answer all codecs supported in this system. This is a collection of codec instances." - - - ^self subclasses inject: self codecs asArray - into: [:result :each | result , each allCodecs] - ] - - GRCodec class >> codecs [ - "Answer a collection of possible codecs of the receiver. To be overridden by concrete subclasses." - - - ^#() - ] - - GRCodec class >> forEncoding: aString [ - "Answer a new codec instance for the given encoding name. Raise an WAUnsupportedEncodingError if the encoding name is not supported by this image." - - - self allSubclassesDo: [:each | - (each supportsEncoding: aString) ifTrue: [ - ^each basicForEncoding: aString]]. - self unsupportedEncoding: aString - ] - - GRCodec class >> supportsEncoding: aString [ - "Answer whether the the given encoding name is supported by this codec class." - - - self subclassResponsibility - ] - - GRCodec class >> basicForEncoding: aString [ - "Create the actual instance." - - - self subclassResponsibility - ] - - GRCodec class >> unsupportedEncoding: aString [ - "Signal an unsupported encoding." - - - GRUnsupportedEncodingError signal: 'unsupported encoding: ' , aString - ] - - name [ - "Answer a human readable string of the receivers encoding policy." - - - self subclassResponsibility - ] - - url [ - "Answer a codec that is responsible to encode and decode URLs. In most cases an UTF-8 codec is the only valid choice, but subclasses might decide to do something else." - - - self subclassResponsibility - ] - - decode: aString [ - - | readStream writeStream | - readStream := self decoderFor: aString readStream. - writeStream := WriteStream on: (String new: aString size). - [readStream atEnd] - whileFalse: [writeStream nextPutAll: (readStream next: 1024)]. - ^writeStream contents - ] - - encode: aString [ - - | writeStream | - writeStream := self encoderFor: - (WriteStream on: (String new: aString size)). - writeStream nextPutAll: aString. - ^writeStream contents - ] - - decoderFor: aReadStream [ - "Wrap aReadStream with an decoder for the codec of the receiver. Answer a read stream that delegates to and shares the state of aReadStream." - - - self subclassResponsibility - ] - - encoderFor: aWriteStream [ - "Wrap aWriteStream with an encoder for the codec of the receiver. Answer a write stream that delegates to and shares the state of aWriteStream." - - - self subclassResponsibility - ] - - printOn: aStream [ - - super printOn: aStream. - aStream - nextPutAll: ' name: '; - print: self name - ] -] - diff --git a/grease/Core/Text/GRCodecStream.st b/grease/Core/Text/GRCodecStream.st deleted file mode 100644 index 14a5da8..0000000 --- a/grease/Core/Text/GRCodecStream.st +++ /dev/null @@ -1,91 +0,0 @@ -GRObject subclass: GRCodecStream [ - | stream | - - - - stream - a WriteStream - - '> - - - GRCodecStream class >> on: aStream [ - - ^self basicNew initalizeOn: aStream - ] - - initalizeOn: aStream [ - - self initialize. - stream := aStream - ] - - binary [ - - - ] - - contents [ - - ^stream contents - ] - - flush [ - - stream flush - ] - - size [ - - ^stream size - ] - - text [ - - - ] - - crlf [ - - self - nextPut: Character cr; - nextPut: Character lf - ] - - next [ - - self subclassResponsibility - ] - - next: anInteger [ - - self subclassResponsibility - ] - - nextPut: aCharacter [ - - self subclassResponsibility - ] - - nextPutAll: aString [ - - self subclassResponsibility - ] - - space [ - - self nextPut: Character space - ] - - tab [ - - self nextPut: Character tab - ] - - atEnd [ - - ^stream atEnd - ] -] diff --git a/grease/Core/Text/GRInflector.st b/grease/Core/Text/GRInflector.st deleted file mode 100644 index 6816e88..0000000 --- a/grease/Core/Text/GRInflector.st +++ /dev/null @@ -1,33 +0,0 @@ -GRObject subclass: GRInflector [ - - - - - InflectionRules := nil. - Uninflected := nil. - - GRInflector class >> pluralize: aString [ - - | string | - string := aString asLowercase. - Uninflected do: [:each | (string endsWith: each) ifTrue: [^aString]]. - InflectionRules do: - [:rule | - (string endsWith: rule first) - ifTrue: [^(aString allButLast: rule third) , rule second]]. - ^aString , 's' - ] - - GRInflector class >> initialize [ - - Uninflected := #('bison' 'bream' 'breeches' 'britches' 'carp' 'chassis' 'clippers' 'cod' 'contretemps' 'corps' 'debris' 'deer' 'diabetes' 'djinn' 'eland' 'elk' 'equipment' 'fish' 'flounder' 'gallows' 'graffiti' 'headquarters' 'herpes' 'high-jinks' 'homework' 'information' 'innings' 'ities' 'itis' 'jackanapes' 'mackerel' 'measles' 'mews' 'money' 'mumps' 'news' 'ois' 'pincers' 'pliers' 'pox' 'proceedings' 'rabies' 'rice' 'salmon' 'scissors' 'sea-bass' 'series' 'shears' 'sheep' 'species' 'swine' 'trout' 'tuna' 'whiting' 'wildebeest'). - InflectionRules := #(#('man' 'en' 2) #('child' 'ren' 0) #('cow' 'kine' 3) #('penis' 'es' 0) #('sex' 'es' 0) #('person' 'ople' 4) #('octopus' 'es' 0) #('quiz' 'zes' 0) #('ox' 'en' 0) #('louse' 'ice' 4) #('mouse' 'ice' 4) #('matrix' 'ices' 2) #('vertix' 'ices' 2) #('vertex' 'ices' 2) #('indix' 'ices' 2) #('index' 'ices' 2) #('x' 'es' 0) #('ch' 'es' 0) #('ss' 'es' 0) #('sh' 'es' 0) #('ay' 's' 0) #('ey' 's' 0) #('iy' 's' 0) #('oy' 's' 0) #('uy' 's' 0) #('y' 'ies' 1) #('alf' 'ves' 1) #('elf' 'ves' 1) #('olf' 'ves' 1) #('arf' 'ves' 1) #('nife' 'ves' 2) #('life' 'ves' 2) #('wife' 'ves' 2) #('sis' 'es' 2) #('tum' 'a' 2) #('ium' 'a' 2) #('buffalo' 'es' 0) #('tomato' 'es' 0) #('buffalo' 'es' 0) #('bus' 'es' 0) #('alias' 'es' 0) #('status' 'es' 0) #('octopus' 'i' 2) #('virus' 'i' 2) #('axis' 'es' 2) #('s' '' 0)) - ] -] - - - -Eval [ - GRInflector initialize -] - diff --git a/grease/Core/Text/GRInvalidUtf8Error.st b/grease/Core/Text/GRInvalidUtf8Error.st deleted file mode 100644 index f1266db..0000000 --- a/grease/Core/Text/GRInvalidUtf8Error.st +++ /dev/null @@ -1 +0,0 @@ -GRError subclass: GRInvalidUtf8Error [] diff --git a/grease/Core/Text/GRMappedPrinter.st b/grease/Core/Text/GRMappedPrinter.st deleted file mode 100644 index 277e78f..0000000 --- a/grease/Core/Text/GRMappedPrinter.st +++ /dev/null @@ -1,36 +0,0 @@ -GRPrinter subclass: GRMappedPrinter [ - | next block | - - - - - GRMappedPrinter class >> block: aBlock next: aPrinter [ - - ^(self new) - block: aBlock; - next: aPrinter; - yourself - ] - - block: aBlock [ - - block := aBlock - ] - - next: aPrinter [ - - next := aPrinter - ] - - initialize [ - - super initialize. - self block: [:value | value] - ] - - print: anObject on: aStream [ - - next print: (block value: anObject) on: aStream - ] -] - diff --git a/grease/Core/Text/GRNullCodec.st b/grease/Core/Text/GRNullCodec.st deleted file mode 100644 index 3a6feb0..0000000 --- a/grease/Core/Text/GRNullCodec.st +++ /dev/null @@ -1,61 +0,0 @@ -GRCodec subclass: GRNullCodec [ - - - - - GRNullCodec class >> codecs [ - - ^Array with: self new - ] - - GRNullCodec class >> supportsEncoding: aString [ - - ^aString isNil - ] - - GRNullCodec class >> basicForEncoding: aString [ - - ^self new - ] - - name [ - - ^'(none)' - ] - - url [ - "The selfish method. Let's do it with ourselves." - - - ^self - ] - - decode: aString [ - "Overridden for efficencey." - - - ^aString - ] - - encode: aString [ - "Overridden for efficencey." - - - ^aString - ] - - decoderFor: aReadStream [ - "wrap to avoid String vs ByteArray issues" - - - ^GRNullCodecStream on: aReadStream - ] - - encoderFor: aWriteStream [ - "wrap to avoid String vs ByteArray issues" - - - ^GRNullCodecStream on: aWriteStream - ] -] - diff --git a/grease/Core/Text/GRNullCodecStream.st b/grease/Core/Text/GRNullCodecStream.st deleted file mode 100644 index 253f277..0000000 --- a/grease/Core/Text/GRNullCodecStream.st +++ /dev/null @@ -1,37 +0,0 @@ -GRCodecStream subclass: GRNullCodecStream [ - - - - stream - - a WriteStream on a String'> - - - next [ - - ^stream next - ] - - next: anInteger [ - - ^stream next: anInteger - ] - - nextPut: aCharacterOrByte [ - - aCharacterOrByte isCharacter - ifTrue: [stream nextPut: aCharacterOrByte] - ifFalse: [stream nextPut: (Character value: aCharacterOrByte)] - ] - - nextPutAll: aStringOrByteArray [ - - aStringOrByteArray isString - ifTrue: [stream nextPutAll: aStringOrByteArray] - ifFalse: [1 - to: aStringOrByteArray size - do: [:index | stream nextPut: (Character value: (aStringOrByteArray at: index))]] - ] -] diff --git a/grease/Core/Text/GRNumberPrinter.st b/grease/Core/Text/GRNumberPrinter.st deleted file mode 100644 index a30bf59..0000000 --- a/grease/Core/Text/GRNumberPrinter.st +++ /dev/null @@ -1,228 +0,0 @@ -GRPrinter subclass: GRNumberPrinter [ - | characters base delimiter digits infinite nan padding accuracy precision separator | - - - base: - delimiter: - digits: - infinite: - nan: - padding: - precision: - separator: '> - - - NumbersToCharactersLowercase := nil. - NumbersToCharactersUppercase := nil. - - GRNumberPrinter class >> initialize [ - - NumbersToCharactersLowercase := '0123456789abcdefghijklmnopqrstuvwxyz'. - NumbersToCharactersUppercase := '0123456789ABCDEFGHIJKLMNOPQRSTUVWXYZ' - ] - - accuracy: aFloat [ - "Round towards the nearest number that is a multiple of aFloat." - - - accuracy := aFloat - ] - - base: anInteger [ - "The numeric base to which the number should be printed." - - - base := anInteger - ] - - characters: aString [ - "The characters to be used to convert a number to a string." - - - characters := aString - ] - - delimiter: aCharacter [ - "The delimiter to separate the integer and fraction part of the number." - - - delimiter := aCharacter - ] - - digits: anInteger [ - "The number of digits to be printed in the integer part." - - - digits := anInteger - ] - - infinite: aString [ - "The string that should be displayed if the number is positive or negative infinity." - - - infinite := aString - ] - - nan: aString [ - "The string that should be displayed if the number is not a number." - - - nan := aString - ] - - padding: aCharacter [ - "The padding for the integer part." - - - padding := aCharacter - ] - - precision: anInteger [ - "The number of digits to be printed in the fraction part." - - - precision := anInteger - ] - - separator: aCharacter [ - "Separator character to be used to group digits." - - - separator := aCharacter - ] - - lowercase [ - "Use lowercase characters for numbers of base 10 and higher." - - - self characters: NumbersToCharactersLowercase - ] - - uppercase [ - "Use uppercase characters for numbers of base 10 and higher." - - - self characters: NumbersToCharactersUppercase - ] - - initialize [ - - super initialize. - self lowercase. - self base: 10. - self delimiter: $.. - self infinite: 'Infinite'. - self nan: 'NaN'. - self padding: $ . - self precision: 0 - ] - - print: aNumber on: aStream [ - - aNumber isNaN ifTrue: [^self printNaN: aNumber on: aStream]. - aNumber isInfinite ifTrue: [^self printInfinite: aNumber on: aStream]. - precision = 0 - ifTrue: [self printInteger: aNumber on: aStream] - ifFalse: [self printFloat: aNumber on: aStream] - ] - - printFloat: aNumber on: aStream [ - - | multiplier rounded | - multiplier := base asFloat raisedTo: precision. - rounded := aNumber roundTo: (accuracy ifNil: [1.0 / multiplier]). - self printInteger: rounded on: aStream. - delimiter isNil ifFalse: [aStream nextPut: delimiter]. - self printFraction: rounded fractionPart abs * multiplier on: aStream - ] - - printFraction: aNumber on: aStream [ - - | result | - result := self - pad: (self digitsOf: aNumber rounded base: base) - left: $0 - to: precision. - separator isNil ifFalse: [result := self separate: result left: separator]. - aStream nextPutAll: result - ] - - printInfinite: aNumber on: aStream [ - - infinite isNil ifFalse: [aStream nextPutAll: infinite] - ] - - printInteger: aNumber on: aStream [ - - | result | - result := self digitsOf: aNumber integerPart base: base. - separator isNil - ifFalse: [result := self separate: result right: separator]. - (digits isNil or: [padding isNil]) - ifFalse: [result := self - pad: result - left: padding - to: digits]. - aStream nextPutAll: result - ] - - printNaN: anInteger on: aStream [ - - nan isNil ifFalse: [aStream nextPutAll: nan] - ] - - digitsOf: aNumber base: aBaseInteger [ - "Answer the absolute digits of aNumber in the base aBaseInteger." - - - | integer stream next | - integer := aNumber truncated abs. - integer = 0 ifTrue: [^'0']. - stream := WriteStream on: (String new: 10). - [integer > 0] whileTrue: - [next := integer quo: aBaseInteger. - stream nextPut: (characters at: 1 + integer - (next * aBaseInteger)). - integer := next]. - ^stream contents reversed - ] - - separate: aString left: aCharacter [ - "Separate from the left side every 3 characters with aCharacter." - - - | size stream | - size := aString size. - stream := WriteStream on: (String new: 2 * size). - 1 - to: size - do: [:index | - (index ~= 1 and: [index \\ 3 = 1]) ifTrue: [stream nextPut: aCharacter]. - stream nextPut: (aString at: index)]. - ^stream contents - ] - - separate: aString right: aCharacter [ - "Separate from the right side every 3 characters with aCharacter." - - - | size stream | - size := aString size. - stream := WriteStream on: (String new: 2 * size). - 1 - to: size - do: [:index | - (index ~= 1 and: [(size - index) \\ 3 = 2]) - ifTrue: [stream nextPut: aCharacter]. - stream nextPut: (aString at: index)]. - ^stream contents - ] -] - - - -Eval [ - GRNumberPrinter initialize -] diff --git a/grease/Core/Text/GROrdinalizePrinter.st b/grease/Core/Text/GROrdinalizePrinter.st deleted file mode 100644 index 3706142..0000000 --- a/grease/Core/Text/GROrdinalizePrinter.st +++ /dev/null @@ -1,24 +0,0 @@ -Eval [ - 'From PharoCore1.0rc1 of 19 October 2009 [Latest update: #10505] on 9 March 2010 at 6:38:04 pm' -] - - - -GRPrinter subclass: GROrdinalizePrinter [ - - - - - print: anObject on: aStream [ - - aStream nextPutAll: (self ordinalize: anObject integerPart) - ] - - ordinalize: anInteger [ - - ^(anInteger \\ 100 between: 11 and: 13) - ifTrue: ['th'] - ifFalse: [#('st' 'nd' 'rd') at: anInteger \\ 10 ifAbsent: ['th']] - ] -] - diff --git a/grease/Core/Text/GRPluggablePrinter.st b/grease/Core/Text/GRPluggablePrinter.st deleted file mode 100644 index ac301bb..0000000 --- a/grease/Core/Text/GRPluggablePrinter.st +++ /dev/null @@ -1,28 +0,0 @@ -GRPrinter subclass: GRPluggablePrinter [ - | block | - - - - - GRPluggablePrinter class >> on: aBlock [ - - ^self new block: aBlock - ] - - block: aBlock [ - - block := aBlock - ] - - initialize [ - - super initialize. - self block: [:value | String new] - ] - - print: anObject on: aStream [ - - aStream nextPutAll: (block value: anObject) - ] -] - diff --git a/grease/Core/Text/GRPrinter.st b/grease/Core/Text/GRPrinter.st deleted file mode 100644 index 0a4a14e..0000000 --- a/grease/Core/Text/GRPrinter.st +++ /dev/null @@ -1,328 +0,0 @@ -GRObject subclass: GRPrinter [ - - - - - GRPrinter class >> cookieTimestamp [ - "Netscape's original proposal defined an Expires header that took a date value in a fixed-length variant format in place of Max-Age: Wdy, DD-Mon-YY HH:MM:SS GMT" - - - ^GRMappedPrinter block: [:timestamp | timestamp asUTC] - next: self abbreviatedWeekName , ', ' , self paddedDay , '-' - , self abbreviatedMonthName , '-' - , self paddedYear , ' ' - , self isoTime , ' GMT' - ] - - GRPrinter class >> httpDate [ - "Answers a printer that formats dates for HTTP1.1 (RFC 2616)" - - - ^self rfc1123 - ] - - GRPrinter class >> isoDate [ - "Ansers a printer that formats dates accoring to ISO(YYYY-MM-DD) E.g. - 2003-12-24" - - - ^self paddedYear , $- , self paddedMonth , $- , self paddedDay - ] - - GRPrinter class >> isoTime [ - "Ansers a printer that formats time accoring to ISO(HH:MM:SS) E.g. - 12:23:34" - - - ^self paddedHour24 , $: , self paddedMinute , $: , self paddedSecond - ] - - GRPrinter class >> rfc1123 [ - "Answers a printer that formats dates for HTTP1.1 (RFC 1123). Eg. - Sun, 06 Nov 1994 08:49:37 GMT" - - - ^GRMappedPrinter block: - [:date | - "For the purposes of HTTP, GMT is exactly equal to UTC (Coordinated Universal Time)" - - date asUTC] - next: GRSequentialPrinter new , self abbreviatedWeekName , ', ' - , self paddedDay , Character space - , self abbreviatedMonthName , Character space - , self paddedYear , Character space - , self isoTime , ' GMT' - ] - - GRPrinter class >> rfc822 [ - "Answers a privter that formats dates according to RFC 822 (email). Eg. - Sun, 31 Aug 2008 19:41:46 +0200" - - - ^self abbreviatedWeekName , ', ' , self paddedDay , Character space - , self abbreviatedMonthName , Character space - , self paddedYear , Character space - , self isoTime , Character space - , self offsetSign , self absOffsetHoursPadded - , self absOffsetMinutesPadded - ] - - GRPrinter class >> rfc822WithTimeZone: aString [ - "Answers a privter that formats dates according to RFC 822 (email) with the given time zone String. Eg. - Sun, 31 Aug 2008 19:41:46 " - - - ^self abbreviatedWeekName , ', ' , self paddedDay , Character space - , self abbreviatedMonthName , Character space - , self paddedYear , Character space - , self isoTime , Character space - , aString - ] - - GRPrinter class >> swissCurrency [ - - ^GRSequentialPrinter new , 'CHF ' , GRSignPrinter new - , ((GRNumberPrinter new) - separator: $'; - precision: 2; - accuracy: 0.05; - yourself) - ] - - GRPrinter class >> usCurrency [ - - ^GRSignPrinter new , $$ , ((GRNumberPrinter new) - separator: $,; - precision: 2; - yourself) - ] - - GRPrinter class >> abbreviatedMonthName [ - - ^self - monthName: #('Jan' 'Feb' 'Mar' 'Apr' 'May' 'Jun' 'Jul' 'Aug' 'Sep' 'Oct' 'Nov' 'Dec') - ] - - GRPrinter class >> abbreviatedWeekName [ - - ^self weekName: #('Sun' 'Mon' 'Tue' 'Wed' 'Thu' 'Fri' 'Sat') - ] - - GRPrinter class >> absOffsetHoursPadded [ - - ^GRMappedPrinter block: [:date | date offset hours abs] - next: (self numberWithAtLeastDigits: 2) - ] - - GRPrinter class >> absOffsetMinutesPadded [ - - ^GRMappedPrinter block: [:date | date offset minutes abs] - next: (self numberWithAtLeastDigits: 2) - ] - - GRPrinter class >> fullMonthName [ - - ^self - monthName: #('January' 'February' 'March' 'April' 'May' 'June' 'July' 'August' 'September' 'October' 'November' 'December') - ] - - GRPrinter class >> fullWeekName [ - - ^self - weekName: #('Monday' 'Tuesday' 'Wednesday' 'Thursday' 'Friday' 'Saturday' 'Sunday') - ] - - GRPrinter class >> monthName: anArray [ - - ^GRPluggablePrinter on: [:date | anArray at: date monthIndex] - ] - - GRPrinter class >> offsetSign [ - - ^GRMappedPrinter block: [:date | date offset] - next: ((GRSignPrinter new) - positivePrinter: $+; - negativePrinter: $-; - yourself) - ] - - GRPrinter class >> paddedCentury [ - - ^GRMappedPrinter block: [:date | date year \\ 100] - next: (self numberWithAtLeastDigits: 2) - ] - - GRPrinter class >> paddedDay [ - - ^GRMappedPrinter block: [:date | date dayOfMonth] - next: (self numberWithAtLeastDigits: 2) - ] - - GRPrinter class >> paddedMonth [ - - ^GRMappedPrinter block: [:date | date monthIndex] - next: (self numberWithAtLeastDigits: 2) - ] - - GRPrinter class >> paddedYear [ - - ^GRMappedPrinter block: [:date | date year] - next: (self numberWithAtLeastDigits: 4) - ] - - GRPrinter class >> unpaddedCentury [ - - ^GRMappedPrinter block: [:date | date year \\ 100] - next: GRNumberPrinter new - ] - - GRPrinter class >> unpaddedDay [ - - ^GRMappedPrinter block: [:date | date dayOfMonth] next: GRNumberPrinter new - ] - - GRPrinter class >> unpaddedMonth [ - - ^GRMappedPrinter block: [:date | date monthIndex] next: GRNumberPrinter new - ] - - GRPrinter class >> unpaddedYear [ - - ^GRMappedPrinter block: [:date | date year] next: GRNumberPrinter new - ] - - GRPrinter class >> weekName: anArray [ - - ^GRPluggablePrinter on: [:date | anArray at: date dayOfWeek] - ] - - GRPrinter class >> paddedHour12 [ - - ^GRMappedPrinter block: [:time | (time hour - 1) \\ 12 + 1] - next: (self numberWithAtLeastDigits: 2) - ] - - GRPrinter class >> paddedHour24 [ - - ^GRMappedPrinter block: [:time | time hour] - next: (self numberWithAtLeastDigits: 2) - ] - - GRPrinter class >> paddedMinute [ - - ^GRMappedPrinter block: [:time | time minute] - next: (self numberWithAtLeastDigits: 2) - ] - - GRPrinter class >> paddedSecond [ - - ^GRMappedPrinter block: [:time | time second] - next: ((GRNumberPrinter new) - padding: $0; - digits: 2) - ] - - GRPrinter class >> unpaddedHour12 [ - - ^GRMappedPrinter block: [:time | (time hour - 1) \\ 12 + 1] - next: GRNumberPrinter new - ] - - GRPrinter class >> unpaddedHour24 [ - - ^GRMappedPrinter block: [:time | time hour] next: GRNumberPrinter new - ] - - GRPrinter class >> unpaddedMinute [ - - ^GRMappedPrinter block: [:time | time minute] next: GRNumberPrinter new - ] - - GRPrinter class >> unpaddedSecond [ - - ^GRMappedPrinter block: [:time | time second] next: GRNumberPrinter new - ] - - GRPrinter class >> binaryFileSize [ - - ^GRUnitPrinter base: 1024 - units: #('byte' 'bytes' 'KiB' 'MiB' 'GiB' 'TiB' 'PiB' 'EiB' 'ZiB' 'YiB') - ] - - GRPrinter class >> decimalFileSize [ - - ^GRUnitPrinter base: 1000 - units: #('byte' 'bytes' 'kB' 'MB' 'GB' 'TB' 'PB' 'EB' 'ZB' 'YB') - ] - - GRPrinter class >> numberWithAtLeastDigits: anInteger [ - - ^(GRNumberPrinter new) - padding: $0; - digits: anInteger; - yourself - ] - - , aPrinter [ - - ^GRSequentialPrinter new , self , aPrinter - ] - - print: anObject [ - - ^String streamContents: [:stream | self print: anObject on: stream] - ] - - print: anObject on: aStream [ - "Subclasses override this method to produce some output." - - - - ] - - pad: aString center: aCharacter to: anInteger [ - "Pad to the center of aString with aCharacter to at least anInteger characters." - - - | result index | - anInteger <= aString size ifTrue: [^aString]. - index := (anInteger - aString size) // 2. - result := (String new: anInteger) atAllPut: aCharacter. - result - replaceFrom: index + 1 - to: index + aString size - with: aString - startingAt: 1. - ^result - ] - - pad: aString left: aCharacter to: anInteger [ - "Pad to the left side of aString with aCharacter to at least anInteger characters." - - - | result | - anInteger <= aString size ifTrue: [^aString]. - result := (String new: anInteger) atAllPut: aCharacter. - result - replaceFrom: anInteger - aString size + 1 - to: anInteger - with: aString - startingAt: 1. - ^result - ] - - pad: aString right: aCharacter to: anInteger [ - "Pad to the right side of aString with aCharacter to at least anInteger characters." - - - | result | - anInteger <= aString size ifTrue: [^aString]. - result := (String new: anInteger) atAllPut: aCharacter. - result - replaceFrom: 1 - to: aString size - with: aString - startingAt: 1. - ^result - ] -] diff --git a/grease/Core/Text/GRSequentialPrinter.st b/grease/Core/Text/GRSequentialPrinter.st deleted file mode 100644 index fb1b7b4..0000000 --- a/grease/Core/Text/GRSequentialPrinter.st +++ /dev/null @@ -1,22 +0,0 @@ -GRPrinter subclass: GRSequentialPrinter [ - | parts | - - - - - initialize [ - - super initialize. - parts := OrderedCollection new - ] - - , aConverter [ - - parts add: aConverter - ] - - print: anObject on: aStream [ - - parts do: [:each | each print: anObject on: aStream] - ] -] diff --git a/grease/Core/Text/GRSignPrinter.st b/grease/Core/Text/GRSignPrinter.st deleted file mode 100644 index 50cbf9a..0000000 --- a/grease/Core/Text/GRSignPrinter.st +++ /dev/null @@ -1,35 +0,0 @@ -GRPrinter subclass: GRSignPrinter [ - | negativePrinter positivePrinter | - - - - - negativePrinter: aPrinter [ - "The printer to be used when the number is negative." - - - negativePrinter := aPrinter - ] - - positivePrinter: aPrinter [ - "The printer to be used when the number is zero or positive." - - - positivePrinter := aPrinter - ] - - initialize [ - - super initialize. - self negativePrinter: $-. - self positivePrinter: nil - ] - - print: anObject on: aStream [ - - anObject negative - ifTrue: [negativePrinter print: anObject on: aStream] - ifFalse: [positivePrinter print: anObject on: aStream] - ] -] - diff --git a/grease/Core/Text/GRStringPrinter.st b/grease/Core/Text/GRStringPrinter.st deleted file mode 100644 index 4433ed6..0000000 --- a/grease/Core/Text/GRStringPrinter.st +++ /dev/null @@ -1,106 +0,0 @@ -GRPrinter subclass: GRStringPrinter [ - | trim length pad character | - - - - - character: aCharacter [ - "The character to pad the string with." - - - character := aCharacter - ] - - length: anInteger [ - "The maximal size of the string, or the size to pad to." - - - length := anInteger - ] - - initialize [ - - super initialize. - self - character: $ ; - length: nil. - self - trimNone; - padNone - ] - - padCenter [ - "Pad to the center." - - - pad := #pad:center:to: - ] - - padLeft [ - "Pad to the left." - - - pad := #pad:left:to: - ] - - padNone [ - "Do not pad the input." - - - pad := nil - ] - - padRight [ - "Pad to the right." - - - pad := #pad:right:to: - ] - - print: anObject on: aStream [ - - | string | - string := anObject greaseString. - trim isNil ifFalse: [string := string perform: trim]. - length isNil - ifFalse: [ - length < string size ifTrue: [string := string copyFrom: 1 to: length]. - (pad isNil or: [character isNil]) - ifFalse: [ - string := self - perform: pad - with: string - with: character - with: length]]. - aStream nextPutAll: string - ] - - trimBoth [ - "Trim to the left and to the right." - - - trim := #trimBoth - ] - - trimLeft [ - "Trim to the left and to the right." - - - trim := #trimLeft - ] - - trimNone [ - "Do not trim the input." - - - trim := nil - ] - - trimRight [ - "Trim to the left and to the right." - - - trim := #trimRight - ] -] - diff --git a/grease/Core/Text/GRUnitPrinter.st b/grease/Core/Text/GRUnitPrinter.st deleted file mode 100644 index 08d1b3f..0000000 --- a/grease/Core/Text/GRUnitPrinter.st +++ /dev/null @@ -1,82 +0,0 @@ -Eval [ - 'From PharoCore1.0rc1 of 19 October 2009 [Latest update: #10505] on 9 March 2010 at 6:45:25 pm' -] - - - -GRPrinter subclass: GRUnitPrinter [ - | integerPrinter fractionPrinter units base | - - - - - GRUnitPrinter class >> base: anInteger units: anArray [ - - ^(self new) - base: anInteger; - units: anArray; - yourself - ] - - base: anInteger [ - - base := anInteger - ] - - fractionPrinter: aPrinter [ - - fractionPrinter := aPrinter - ] - - integerPrinter: aPrinter [ - - integerPrinter := aPrinter - ] - - units: anArray [ - - units := anArray - ] - - initialize [ - - super initialize. - self integerPrinter: ((GRNumberPrinter new) - precision: 0; - yourself). - self fractionPrinter: ((GRNumberPrinter new) - precision: 1; - yourself) - ] - - print: anObject on: aStream [ - - anObject = 1 - ifTrue: - [^self - print: anObject - unit: units first - on: aStream]. - units allButFirst inject: anObject asFloat - into: - [:value :each | - value < base - ifFalse: [value / base] - ifTrue: - [^self - print: value - unit: each - on: aStream]] - ] - - print: aNumber unit: aString on: aStream [ - - (units first = aString or: [units second = aString]) - ifTrue: [integerPrinter print: aNumber on: aStream] - ifFalse: [fractionPrinter print: aNumber on: aStream]. - aStream - nextPut: $ ; - nextPutAll: aString - ] -] - diff --git a/grease/Core/Text/GRUnsupportedEncodingError.st b/grease/Core/Text/GRUnsupportedEncodingError.st deleted file mode 100644 index fc53019..0000000 --- a/grease/Core/Text/GRUnsupportedEncodingError.st +++ /dev/null @@ -1,6 +0,0 @@ -GRError subclass: GRUnsupportedEncodingError [ - - - -] - diff --git a/grease/Core/Utilities/GRBoundDelayedSend.st b/grease/Core/Utilities/GRBoundDelayedSend.st deleted file mode 100644 index e1b882f..0000000 --- a/grease/Core/Utilities/GRBoundDelayedSend.st +++ /dev/null @@ -1,48 +0,0 @@ -GRDelayedSend subclass: GRBoundDelayedSend [ - | arguments | - - - - arguments - - the predefined arguments'> - - - argumentCount [ - - ^selector numArgs - arguments size - ] - - valueWithArguments: anArray [ - - ^arguments size + anArray size = selector numArgs - ifTrue: [receiver perform: selector withArguments: arguments , anArray] - ifFalse: [self invalidArgumentCount] - ] - - valueWithPossibleArguments: anArray [ - - | composed | - ^(composed := arguments , anArray) size < selector numArgs - ifTrue: [self invalidArgumentCount] - ifFalse: - [receiver perform: selector - withArguments: (composed first: selector numArgs)] - ] - - initializeWithReceiver: anObject selector: aSymbol arguments: anArray [ - - self initializeWithReceiver: anObject selector: aSymbol. - arguments := anArray asArray - ] - - printOn: aStream [ - - super printOn: aStream. - aStream - nextPutAll: ' arguments: '; - print: arguments - ] -] diff --git a/grease/Core/Utilities/GRDelayedSend.st b/grease/Core/Utilities/GRDelayedSend.st deleted file mode 100644 index e16796e..0000000 --- a/grease/Core/Utilities/GRDelayedSend.st +++ /dev/null @@ -1,104 +0,0 @@ -GRObject subclass: GRDelayedSend [ - | receiver selector | - - - selector: - - receiver - - the object receiving the message - - selector - - the message selector sent to the receiver'> - - - GRDelayedSend class >> receiver: anObject selector: aSymbol [ - - ^GRUnboundDelayedSend basicNew initializeWithReceiver: anObject - selector: aSymbol - ] - - GRDelayedSend class >> receiver: anObject selector: aSymbol argument: aParameter [ - - ^self - receiver: anObject - selector: aSymbol - arguments: (Array with: aParameter) - ] - - GRDelayedSend class >> receiver: anObject selector: aSymbol arguments: anArray [ - - ^GRBoundDelayedSend basicNew - initializeWithReceiver: anObject - selector: aSymbol - arguments: anArray - ] - - argumentCount [ - "Answer the number of arguments that must be provided to the receiver when sending it." - - - self subclassResponsibility - ] - - fixCallbackTemps [ - "For polymorphism with BlockContext>>#fixCallbackTemps." - - - - ] - - value [ - - ^self valueWithArguments: #() - ] - - value: anObject [ - - ^self valueWithArguments: (Array with: anObject) - ] - - value: aFirstObject value: aSecondObject [ - - ^self valueWithArguments: (Array with: aFirstObject with: aSecondObject) - ] - - valueWithArguments: anArray [ - - self subclassResponsibility - ] - - valueWithPossibleArguments: anArray [ - - self subclassResponsibility - ] - - initializeWithReceiver: anObject selector: aSymbol [ - - self initialize. - receiver := anObject. - selector := aSymbol - ] - - printOn: aStream [ - - super printOn: aStream. - aStream - nextPutAll: ' receiver: '; - print: receiver. - aStream - nextPutAll: ' selector: '; - print: selector - ] - - invalidArgumentCount [ - - GRInvalidArgumentCount signal - ] -] diff --git a/grease/Core/Utilities/GRInvalidArgumentCount.st b/grease/Core/Utilities/GRInvalidArgumentCount.st deleted file mode 100644 index 8129bb3..0000000 --- a/grease/Core/Utilities/GRInvalidArgumentCount.st +++ /dev/null @@ -1,6 +0,0 @@ -GRError subclass: GRInvalidArgumentCount [ - - - -] - diff --git a/grease/Core/Utilities/GRUnboundDelayedSend.st b/grease/Core/Utilities/GRUnboundDelayedSend.st deleted file mode 100644 index 470c095..0000000 --- a/grease/Core/Utilities/GRUnboundDelayedSend.st +++ /dev/null @@ -1,25 +0,0 @@ -GRDelayedSend subclass: GRUnboundDelayedSend [ - - - - - argumentCount [ - - ^selector numArgs - ] - - valueWithArguments: anArray [ - - ^anArray size = selector numArgs - ifTrue: [receiver perform: selector withArguments: anArray] - ifFalse: [self invalidArgumentCount] - ] - - valueWithPossibleArguments: anArray [ - - ^anArray size < selector numArgs - ifTrue: [self invalidArgumentCount] - ifFalse: [self valueWithArguments: (anArray first: selector numArgs)] - ] -] - diff --git a/grease/GST/Core/Extensions.st b/grease/GST/Core/Extensions.st deleted file mode 100644 index c87e953..0000000 --- a/grease/GST/Core/Extensions.st +++ /dev/null @@ -1,394 +0,0 @@ -GRPackage class extend [ - - greaseGSTCore [ - - ^(self new) - name: 'Grease-GST-Core'; - addDependency: 'Grease-Core'; - url: #gstUrl; - yourself - ] - - greaseTestsGSTCore [ - - ^(self new) - name: 'Grease-Tests-GST-Core'; - description: 'Unit tests for the package Grease-GST-Core.'; - addDependency: 'Grease-GST-Core'; - addDependency: 'Grease-Tests-Core'; - url: #gstUrl; - yourself - ] -] - -GRPackage extend [ - - gstUrl [ - - ^'http://git.savannah.gnu.org/r/smalltalk.git/' - ] -] - -Object extend [ - - isEmptyOrNil [ - - ^false - ] -] - -Collection extend [ - - isEmptyOrNil [ - - ^self isEmpty - ] -] - -Interval extend [ - -] - -UndefinedObject extend [ - - isEmptyOrNil [ - - ^true - ] -] - -BlockClosure extend [ - - fixCallbackTemps [ - - ] -] - -Behavior extend [ - - fullName [ - - ^self nameIn: Smalltalk - ] - - startUp: aBoolean [ - "StartUo/ShutDown. See GRGSTPlatform class methods about startUpList and shutDownList" - - ] - - shutDown: aBoolean [ - "StartUo/ShutDown. See GRGSTPlatform class methods about startUpList and shutDownList" - - ] -] - -Time class extend [ - - totalSeconds [ - - ^self secondClock - ] -] - -Date class extend [ - - year: y month: m day: d [ - - ^self new setDay: d monthIndex: m year: y - ] -] - -PositionableStream extend [ - - greaseUpToAll: aCollection [ - "Needed for Seaside ports to other dialects where #upToAll: may have - different semantics" - ^ self upToAll: aCollection - ] -] - -WriteStream extend [ - - crlf [ - - self - nextPut: Character cr; - nextPut: Character lf - ] -] - -Random extend [ - - nextInt: anInteger [ - - anInteger strictlyPositive ifFalse: [ self error: 'Range must be positive' ]. - ^(self next * anInteger) truncated + 1 - ] - -] - -DirectedMessage extend [ - - valueWithPossibleArguments: anArray [ - - | arguments | - arguments := Array new: self selector numArgs. - arguments replaceFrom: 1 - to: (args size min: arguments size) - with: args - startingAt: 1. - arguments size > args size ifTrue: [ - arguments replaceFrom: args size + 1 - to: (args size + anArray size min: arguments size) - with: anArray - startingAt: 1]. - ^self valueWithArguments: arguments - ] -] - -BlockClosure extend [ - - argumentCount [ - - ^self numArgs - ] - - valueWithPossibleArguments: aCollection [ - - | args | - (aCollection size == self numArgs) - ifTrue: [^self valueWithArguments: aCollection]. - args := Array new: self numArgs. - args replaceFrom: 1 - to: (aCollection size min: args size) - with: aCollection - startingAt: 1. - ^self valueWithArguments: args - ] -] - -Symbol extend [ - - - capitalized [ - - ^self asString capitalized asSymbol - ] - - isKeyword [ - - ^self last = $: - ] - - isUnary [ - - ^self isKeyword not and: [ - self first isLetter] - ] - - asMutator [ - - "Return a setter message from a getter message. For example, - #name asMutator returns #name:" - ^ (self copyWith: $:) asSymbol - ] -] - -String extend [ - - reversed [ - - ^self reverse - ] - - beginsWith: aString [ - - ^self startsWith: aString - ] - - sort [ - - self sort: [:a :b | a <= b] - ] - - sort: aBlock [ - - self - replaceFrom: 1 - to: self size - with: (self asSortedCollection: aBlock) asString - startingAt: 1 - ] - - capitalized [ - - | cap | - self isEmpty ifTrue: [^self]. - cap := self copy. - cap at: 1 put: (self at: 1) asUppercase. - ^cap - ] -] - -Character extend [ - - greaseInteger [ - - ^self codePoint - ] - - asUnicode [ - - ^self codePoint - ] -] - -CharacterArray extend [ - - greaseString [ - - ^self asString - ] -] - -Number extend [ - - isFraction [ - - ^false - ] - - weeks [ - - ^Duration weeks: self - ] - - days [ - - ^Duration days: self - ] - - hours [ - - ^Duration hours: self - ] - - minutes [ - - ^Duration minutes: self - ] - - seconds [ - - ^Duration seconds: self - ] - - milliseconds [ - - ^Duration milliseconds: self - ] - - isZero [ - - ^self = 0 - ] -] - -Float class extend [ - - nan [ - - "Why a FloatD?" - ^FloatD nan - ] - - infinity [ - - "Why a FloatD?" - ^FloatD infinity - ] -] - -Collection extend [ - - any [ - - ^self anyOne - ] - - sorted [ - - ^self asArray sort - ] - - sorted: aBlock [ - - ^self asArray sort: aBlock - ] - - isCollection [ - - ^true - ] -] - -Object extend [ - printStringLimitedTo: anInteger [ - "Answer a String representing the receiver, without making it longer - than anInteger characters" - - - | stream | - stream := WriteStream on: String new. - self printOn: stream. - ^stream position > anInteger - ifTrue: [ (stream copyFrom: 0 to: anInteger - 4), '...' ] - ifFalse: [ stream contents ] - ] -] - -Duration extend [ - - milliseconds [ - - ^0 - ] -] - -BlockClosure extend [ - fixCallbackTemps [ - - outerContext isNil ifTrue: [^self]. - ^self shallowCopy outerContext: outerContext fixCallbackTemps; yourself - ] -] - -BlockContext extend [ - fixCallbackTemps [ - - outerContext isNil ifTrue: [^self shallowCopy]. - ^self shallowCopy outerContext: outerContext fixCallbackTemps; yourself - ] -] - -ContextPart extend [ - fixCallbackTemps [ - - ^self shallowCopy - ] -] - -DirectedMessage extend [ - argumentCount [ - "Answer the number of missing arguments to complete the number required - by the receiver's selector" - - - ^self selector numArgs - self arguments size - ] - - fixCallbackTemps [ - - ^self - ] -] diff --git a/grease/GST/Core/GRGSTGenericCodec.st b/grease/GST/Core/GRGSTGenericCodec.st deleted file mode 100644 index fd6d60a..0000000 --- a/grease/GST/Core/GRGSTGenericCodec.st +++ /dev/null @@ -1,86 +0,0 @@ -GRCodec subclass: GRGSTGenericCodec [ - | encoding urlCodec | - - - - - GRGSTGenericCodec class [ - - basicForEncoding: aString [ - - (self supportsEncoding: aString) - ifFalse: [self unsupportedEncoding: aString]. - ^self basicNew initializeWithEncoding: aString - ] - - supportedEncodingNames [ - "answers the names of the encodings supported by this class" - - - ^#('UTF-8') - ] - - codecs [ - - ^self supportedEncodingNames collect: [:each | - self basicForEncoding: each] - ] - - supportsEncoding: aString [ - "Answer whether the the given encoding name is supported." - - - ^true - "^self supportedEncodingNames includes: aString" - ] -] - - - decoderFor: aStream [ - - ^(I18N.EncodedStream unicodeOn: aStream encoding: encoding) - ] - - encoderFor: aStream [ - - aStream species == ByteArray - ifTrue: [ ^self encoderFor: aStream contents asString ]. - ^aStream species == UnicodeString - ifTrue: [ I18N.EncodedStream encoding: aStream to: encoding ] - ifFalse: [ I18N.EncodedStream on: aStream to: encoding ] - ] - - - decode: aString [ - - ^(self decoderFor: aString readStream) contents - ] - - encode: aString [ - - ^(self encoderFor: aString readStream) contents asString - ] - - initializeWithEncoding: aString [ - - self initialize. - encoding := aString. - urlCodec := self - ] - - name [ - - ^encoding - ] - - url [ - "RFC 3986: When a new URI scheme defines a component that represents - textual data consisting of characters from the Universal Character Set - [UCS], the data should first be encoded as octets according to the UTF-8 - character encoding." - - - ^urlCodec - ] -] - diff --git a/grease/GST/Core/GRGSTPlatform.st b/grease/GST/Core/GRGSTPlatform.st deleted file mode 100644 index 8d28cd5..0000000 --- a/grease/GST/Core/GRGSTPlatform.st +++ /dev/null @@ -1,326 +0,0 @@ -GRPlatform subclass: GRGSTPlatform [ - - - - - GRGSTPlatform class [ - | startUpList shutdownList | - - initialize [ - - startUpList := OrderedCollection new. - shutdownList := OrderedCollection new. - self select - ] - - unload [ - - self unselect - ] - - update: anAspect [ - - anAspect == #returnFromSnapshot ifTrue: [ - startUpList do: [:each | each startUp: true]]. - anAspect == #aboutToQuit ifTrue: [ - shutdownList do: [:each | each shutDown: true]] - ] - - addToStartUpList: anObject [ - - (startUpList includes: anObject) ifFalse: [ - startUpList add: anObject] - ] - - addToShutDownList: anObject [ - - (shutdownList includes: anObject) ifFalse: [ - shutdownList add: anObject] - ] - - removeFromStartUpList: anObject [ - - (startUpList includes: anObject) ifTrue: [ - startUpList remove: anObject] - ] - - removeFromShutDownList: anObject [ - - (shutdownList includes: anObject) ifTrue: [ - shutdownList remove: anObject] - ] - ] - - newline [ - "Answer the system's default newline character (sequence)." - - - ^' -' - ] - - addToShutDownList: anObject [ - "Add anObject to the shutdown-list of the system. On shutdown the - message #shutDown will be sent to anObject." - - - self class addToShutDownList: anObject - ] - - addToStartUpList: anObject [ - "Add anObject to the startup-list of the system. On startup the message - #startUp will be sent to anObject." - - - self class addToStartUpList: anObject - ] - - removeFromShutDownList: anObject [ - "Remove anObject from the shutdown list in the system." - - - self class removeFromShutDownList: anObject - ] - - removeFromStartUpList: anObject [ - "Remove anObject from the startup list in the system." - - - self class removeFromStartUpList: anObject - ] - - asMethodReturningByteArray: aByteArrayOrString named: aSymbol [ - "Generates the source of a method named aSymbol that returns - aByteArrayOrString as a ByteArray" - - - ^String streamContents: [ :stream | - stream nextPutAll: aSymbol; nextPutAll: ' [ '; nl. - stream tab; nextPutAll: ' ^#['. - aByteArrayOrString asByteArray - do: [ :each | each printOn: stream ] - separatedBy: [ stream space ]. - stream nextPutAll: ']'; nl; nextPutAll: ']' ] - ] - - compile: aString into: aClass classified: aSymbol [ - - aClass compile: aString classified: aSymbol - ] - - contentsOfFile: aString binary: aBoolean [ - - | data | - data := (File name: aString) contents. - aBoolean ifTrue: [ data := data asByteArray ]. - ^data - ] - - convertToSmalltalkNewlines: aString [ - "Convert any line endings (CR, CRLF, LF) to CR." - - - aString isNil ifTrue: [ ^ nil ]. - ^aString class streamContents: [ :writeStream | - | readStream | - readStream := aString readStream. - [ readStream atEnd ] whileFalse: [ - | next | - next := readStream next. - next = Character cr - ifTrue: [ - readStream peek = Character lf - ifTrue: [ readStream skip: 1 ]. - writeStream nextPut: Character cr ] - ifFalse: [ - next = Character lf - ifTrue: [ writeStream nextPut: Character cr ] - ifFalse: [ writeStream nextPut: next ] ] ] ] - ] - - ensureExistenceOfFolder: aString [ - "creates a folder named aString in the image directory" - - - (Directory image / aString) create - ] - - filesIn: aPathString [ - "Return a collection of absolute paths for all the files (no directories) in the directory given by aPathString - must not include file names that start with ." - - - | directory | - directory := File name: aPathString. - ^(directory files - reject: [:each | each name first = $.]) - collect: [:each | each asString] - ] - - localNameOf: aFilename [ - - ^File stripPathFrom: aFilename - ] - - removeSelector: aSymbol from: aClass [ - - aClass removeSelector: aSymbol - ] - - write: aStringOrByteArray toFile: aFileNameString inFolder: aFolderString [ - "writes aStringOrByteArray to a file named aFilenameString in the folder aFolderString" - - - | stream fileName | - aFolderString / aFileNameString withWriteStreamDo: [ :stream | - stream nextPutAll: aStringOrByteArray ] - ] - - base64Decode: aString [ - - | codeChars decoder output index nl endChars end limit padding data sz | - codeChars := 'ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/'. - decoder := (0 to: 255) - collect: [:n | (codeChars indexOf: (n + 1) asCharacter) - 1]. - decoder replaceAll: -1 with: 0. - output := (data := String new: aString size * 3 // 4) - writeStream. - index := 1. - nl := Character nl. - "There is padding at the end of a base64 message if the content is not a multiple of - 3 bytes in length. The padding is either two ='s to pad-out a trailing byte, 1 = to - pad out a trailing pair of bytes, or no padding. Here we count the padding. After - processing the message we cut-back by the amount of padding." - sz := end := aString size. - endChars := codeChars , (String with: $=). - - [(endChars includes: (aString at: end)) - and: [end = sz or: [(aString at: end + 1) = nl]]] - whileFalse: [end := end - 1]. - limit := end. - padding := 0. - [(aString at: end) == $=] whileTrue: - [padding := padding - 1. - end := end - 1]. - [index <= limit] whileTrue: - [| triple | - triple := ((decoder at: (aString at: index) asInteger) bitShift: 18) - + ((decoder at: (aString at: index + 1) asInteger) bitShift: 12) - + ((decoder at: (aString at: index + 2) asInteger) bitShift: 6) - + (decoder at: (aString at: index + 3) asInteger). - output nextPut: (Character value: (triple digitAt: 3)). - output nextPut: (Character value: (triple digitAt: 2)). - output nextPut: (Character value: (triple digitAt: 1)). - index := index + 4. - [(index > sz or: [(aString at: index) = nl]) and: [index <= limit]] - whileTrue: [index := index + 1]]. - padding ~= 0 ifTrue: [output skip: padding]. - ^data copyFrom: 1 to: output position - ] - - isProcessTerminated: aProcess [ - "Return a boolean indicating whether aProcess has been terminated." - - - ^aProcess isTerminated - ] - - terminateProcess: aProcess [ - "Permanently terminate the process, unwinding first to execute #ensure: - and #ifCurtailed: blocks." - - - aProcess terminate - ] - - label [ - - ^'GNU Smalltalk' - ] - - newRandom [ - "Answers the random number generator to be used to create session and - continuation keys. Make sure it is seeded. They only methods that will - be sent to it are: - #nextInt: - should answer a random integer in the interval [1, anInteger] - #randomFrom: - should answer a random element from the given collection - - Make sure that both methods are safe under heavy concurrent load. - - Used by Gemstone/S traditional Randoms which cannot be persisted. - Used by Squeak to use a secure random when avaiable." - - - ^GRGSTRandomProvider - ] - - readWriteByteStream [ - "ByteArray based read write stream" - - - ^ReadWriteStream on: ByteArray new - ] - - readWriteCharacterStream [ - "String based read write stream" - - - ^ReadWriteStream on: '' - ] - - semaphoreClass [ - "used by Gemstone/S traditional Semaphores which cannot be persisted" - - - ^Semaphore - ] - - weakDictionaryOfSize: aNumber [ - - ^WeakKeyIdentityDictionary new: aNumber - ] - - openDebuggerOn: anError [ - - | process | - process := Processor activeProcess. - "If we are running in the UI process, we don't want to suspend the active process. The - error was presumably triggered while stepping in the Debugger. If we simply immediately - signal an UnhandledError, the debugger will catch this and display the signaling context. - It isn't perfect or pretty but it works." - (ProcessBrowser isUIProcess: process) - ifTrue: [UnhandledError signalForException: anError] - ifFalse: - [WorldState addDeferredUIMessage: - [process - debug: anError signalerContext - title: anError description - full: true]. - process suspend] - ] - - stackDepth [ - - | depth current | - depth := 0. - current := thisContext. - [current isNil] whileFalse: - [current := current parentContext. - depth := depth + 1]. - ^depth - 1 - ] - - secureHashFor: aString [ - - ^MD5 digestOf: aString - ] -] - - - -Eval [ - GRGSTPlatform initialize -] - diff --git a/grease/GST/Core/GRGSTRandomProvider.st b/grease/GST/Core/GRGSTRandomProvider.st deleted file mode 100644 index fcc5d61..0000000 --- a/grease/GST/Core/GRGSTRandomProvider.st +++ /dev/null @@ -1,60 +0,0 @@ -GRObject subclass: GRGSTRandomProvider [ - - - - - GRGSTRandomProvider class [ - | mutex generator | - - ] - - GRGSTRandomProvider class >> initialize [ - - GRPlatform current addToStartUpList: self. - self startUp - ] - - GRGSTRandomProvider class >> randomClass [ - - ^Random - ] - - GRGSTRandomProvider class >> unload [ - - GRPlatform current removeFromStartUpList: self - ] - - GRGSTRandomProvider class >> nextInt: anInteger [ - "Answer a random integer in the interval [1, anInteger]" - - - ^mutex critical: [generator nextInt: anInteger] - ] - - GRGSTRandomProvider class >> randomFrom: aCollection [ - - | random count | - random := self nextInt: aCollection size. - ^aCollection isSequenceable - ifTrue: [aCollection at: random] - ifFalse: - [count := 1. - aCollection do: - [:ea | - count = random ifTrue: [^ea]. - count := count + 1]] - ] - - GRGSTRandomProvider class >> startUp [ - - generator := self randomClass new. - mutex := Semaphore forMutualExclusion - ] -] - - - -Eval [ - GRGSTRandomProvider initialize -] - diff --git a/grease/PORTING b/grease/PORTING deleted file mode 100644 index b3a8b6a..0000000 --- a/grease/PORTING +++ /dev/null @@ -1,4 +0,0 @@ -Grease-Core-obi.30 -Grease-Pharo-Core-pmm.13 -Grease-Tests-Core-pmm.39 -Grease-Tests-Pharo-Core-lr.6 diff --git a/grease/PackageBuilder.st b/grease/PackageBuilder.st deleted file mode 100755 index a926ad1..0000000 --- a/grease/PackageBuilder.st +++ /dev/null @@ -1,312 +0,0 @@ -#!/usr/bin/env gst -" -PackageBuilder.st -by Stefan Schmiedl -with ideas from Nico and Gwen - -usage: -PackageBuilder new - name: 'Iliad-Core'; - namespace: 'Iliad'; - prereq: 'Sport'; - prereq: 'Iconv'; - ... - testBuilder: (TestBuilder on: 'Tests' withExtension: '.st'); - filein: 'Utilities/IliadObject.st'; - filein: 'Utilities/Support.st'; - ... - buildXml -" - -Object subclass: Indenter [ - - |stream indent indentString| - - Indenter class >> on: aStream [ - - - ^ self new on: aStream - ] - - on: aStream [ - - - stream := aStream. - indent := ''. - indentString := ' ' - ] - - indent [ - - - stream nextPutAll: indent - ] - - indentMore [ - - - indent := indent , indentString - ] - - indentLess [ - - - ( indent size < indentString size ) - ifTrue: [ indent := '' ] - ifFalse: [ - indent := indent allButLast: indentString size - ] - ] - - nextPutAll: aString [ - - stream nextPutAll: aString - ] - - nextPut: aChar [ - - stream nextPut: aChar - ] - - tag: aString [ - - to stream.'> - stream nextPut: $<; nextPutAll: aString; nextPut: $> - ] - - indentNl: aBlock [ - - - self indent. - aBlock cull: stream. - stream nl - ] - - wrap: aString do: aBlock [ - - - self indentNl: [ self tag: aString ]. - self indentMore. - aBlock value. - self indentLess. - self indentNl: [ self tag: '/',aString ]. - ] - - wrap: aString around: contentString [ - - - contentString ifNotNil: [ - self indentNl: [ :aStream | - self - tag: aString; - nextPutAll: contentString; - tag: '/',aString]] - ] - - wrap: aString aroundEachOf: aCollection [ - - - aCollection do: [ :item | self wrap: aString around: item ] - ] -] - - -Object subclass: TestBuilder [ - - | testroot pattern namespace | - - testroot [ - - ^ testroot - ] - testroot: aString [ - - testroot := File name: aString - ] - pattern [ - - ^ pattern - ] - pattern: aString [ - - pattern := aString - ] - namespace [ - - ^ namespace - ] - namespace: aString [ - - namespace := aString - ] - - collectFiles [ - - - |files| - files := OrderedCollection new. - ( self testroot ) allFilesMatching: self pattern do: [ :f | - files add: f - ]. - ^ files - ] - - collectTestsIn: aCollection [ - - - |tests| - tests := OrderedCollection new. - aCollection do: [ :file | - file contents onOccurrencesOfRegex: 'subclass: (.*Test)' do: [ :rr | - tests add: ( rr at: 1 ) - ] - ]. - ^ tests - ] - - renderTests: aCollection on: aStream [ - - - aStream wrap: 'sunit' do: [ - aCollection do: [ :tc | - aStream indentNl: [ - aStream - nextPutAll: self namespace; - nextPut: $.; - nextPutAll: tc - ] - ] - ] - ] - - renderXmlOn: aStream [ - - - aStream wrap: 'test' do: [ |files tests paths| - files := self collectFiles. - tests := self collectTestsIn: files. - paths := files collect: [ :f | self testroot parent pathTo: f ]. - aStream wrap: 'filein' aroundEachOf: paths. - aStream wrap: 'file' aroundEachOf: paths. - self renderTests: tests on: aStream. - ] - ] -] - - -Object subclass: PackageBuilder [ - |name url namespace prereqs provides testBuilder start fileins resources| - - PackageBuilder class >> new [ - ^ self basicNew initialize - ] - - initialize [ - prereqs := OrderedCollection new. - provides := OrderedCollection new. - fileins := OrderedCollection new. - resources := OrderedCollection new. - ] - - name [ - - ^ name - ] - name: aString [ - - name := aString - ] - url [ - - ^ url - ] - url: aString [ - - url := aString - ] - namespace [ - - ^ namespace - ] - namespace: aString [ - - namespace := aString - ] - prereqs [ - - ^ prereqs - ] - prereq: aString [ - - prereqs add: aString - ] - provides [ - - ^ provides - ] - provides: aString [ - - provides add: aString - ] - start [ - - ^ start - ] - start: aString [ - - start := aString - ] - fileins [ - - ^ fileins - ] - filein: aString [ - - fileins add: aString - ] - - resource: aString [ - - resources add: aString - ] - - testsBelow: aDirname matching: aPattern [ - - - testBuilder := - TestBuilder new - testroot: aDirname; - pattern: aPattern; - namespace: self namespace. - ] - - renderXmlOn: aStream [ - - - aStream wrap: 'package' do: [ - aStream - wrap: 'name' around: self name; - wrap: 'url' around: self url; - wrap: 'namespace' around: self namespace. - self prereqs do: [ :p | aStream wrap: 'prereq' around: p ]. - self provides do: [ :p | aStream wrap: 'provides' around: p ]. - testBuilder ifNotNil: [ testBuilder renderXmlOn: aStream ]. - aStream wrap: 'filein' aroundEachOf: fileins. - aStream wrap: 'file' aroundEachOf: fileins. - aStream wrap: 'file' aroundEachOf: resources. - aStream wrap: 'start' around: start. - ] - ] - - buildXml [ - - - self renderXmlOn: ( Indenter on: FileStream stdout ) - ] - -] - - -Eval [ - Smalltalk arguments do: [ :filename | FileStream fileIn: filename ] -] diff --git a/grease/README b/grease/README deleted file mode 100644 index e69de29..0000000 diff --git a/grease/Tests/Core/GRAbstractDictionaryTest.st b/grease/Tests/Core/GRAbstractDictionaryTest.st deleted file mode 100644 index f5691be..0000000 --- a/grease/Tests/Core/GRAbstractDictionaryTest.st +++ /dev/null @@ -1,85 +0,0 @@ -GRCollectionTest subclass: GRAbstractDictionaryTest [ - | associations | - - - - - GRAbstractDictionaryTest class >> isAbstract [ - - ^self name = #GRAbstractDictionaryTest - ] - - allowsDuplicateValues [ - - ^true - ] - - arbitraryAssociations [ - - ^associations ifNil: [associations := self createArbitraryAssociations] - ] - - arbitraryCollection [ - - | dict | - dict := self emptyCollection. - self arbitraryAssociations do: [:each | dict at: each key put: each value]. - ^dict - ] - - createArbitraryAssociations [ - - self subclassResponsibility - ] - - isKey: anObject equivalentTo: anotherObject [ - - self subclassResponsibility - ] - - isExtensible [ - - ^false - ] - - isInitializable [ - - ^false - ] - - isSequenced [ - - ^false - ] - - isSequencedReadable [ - - ^false - ] - - testAssociationsDo [ - - | collection assocs count | - collection := self arbitraryCollection. - assocs := self arbitraryAssociations copy. - count := 0. - collection associationsDo: - [:assoc | - | size | - count := count + 1. - size := assocs size. - assocs := assocs reject: - [:each | - (self isKey: each key equivalentTo: assoc key) - and: [each value = assoc value]]. - self assert: size - 1 = assocs size]. - self assert: assocs isEmpty. - self assert: count = self arbitraryAssociations size - ] - - valuesOf: aCollection [ - - ^aCollection values - ] -] - diff --git a/grease/Tests/Core/GRArrayTest.st b/grease/Tests/Core/GRArrayTest.st deleted file mode 100644 index 6e2dc06..0000000 --- a/grease/Tests/Core/GRArrayTest.st +++ /dev/null @@ -1,36 +0,0 @@ -GRCollectionTest subclass: GRArrayTest [ - - - - - allowsDuplicateValues [ - - ^true - ] - - collectionClass [ - - ^Array - ] - - isExtensible [ - - ^false - ] - - isInitializable [ - - ^true - ] - - isSequenced [ - - ^true - ] - - isSequencedReadable [ - - ^true - ] -] - diff --git a/grease/Tests/Core/GRBagTest.st b/grease/Tests/Core/GRBagTest.st deleted file mode 100644 index c729810..0000000 --- a/grease/Tests/Core/GRBagTest.st +++ /dev/null @@ -1,36 +0,0 @@ -GRCollectionTest subclass: GRBagTest [ - - - - - allowsDuplicateValues [ - - ^true - ] - - collectionClass [ - - ^Bag - ] - - isExtensible [ - - ^true - ] - - isInitializable [ - - ^true - ] - - isSequenced [ - - ^false - ] - - isSequencedReadable [ - - ^false - ] -] - diff --git a/grease/Tests/Core/GRCodecTest.st b/grease/Tests/Core/GRCodecTest.st deleted file mode 100644 index 8b81d7c..0000000 --- a/grease/Tests/Core/GRCodecTest.st +++ /dev/null @@ -1,122 +0,0 @@ -TestCase subclass: GRCodecTest [ - - - - - decodedString [ - - ^'Ãœbèrstrîñgé' - ] - - latin1String [ - - ^self - asString: #(220 98 232 114 115 116 114 238 241 103 233) - ] - - macromanString [ - - ^self - asString: #(134 98 143 114 115 116 114 148 150 103 142) - ] - - utf16beString [ - - ^self - asString: #(0 220 0 98 0 232 0 114 0 115 0 116 0 114 0 238 0 241 0 103 0 233) - ] - - utf16leString [ - - ^self - asString: #(220 0 98 0 232 0 114 0 115 0 116 0 114 0 238 0 241 0 103 0 233 0) - ] - - utf8String [ - - ^self - asString: #(195 156 98 195 168 114 115 116 114 195 174 195 177 103 195 169) - ] - - testAllCodecs [ - - self assert: GRCodec allCodecs notEmpty. - GRCodec allCodecs do: - [:codec | - self deny: codec class = GRCodec. - self assert: (codec isKindOf: GRCodec)] - ] - - testCodecLatin1 [ - - #('iso-8859-1' 'ISO-8859-1') do: - [:each | - | codec | - codec := GRCodec forEncoding: each. - self assert: codec name = each. - self assert: codec url name = each. - self assert: (codec encode: self decodedString) = self latin1String. - self assert: (codec url encode: self decodedString) = self latin1String. - self assert: (codec decode: self latin1String) = self decodedString. - self assert: (codec url decode: self latin1String) = self decodedString] - ] - - testNext [ - - #('iso-8859-1' 'ISO-8859-1') do: - [:each | - | stream | - stream := (GRCodec forEncoding: each) - encoderFor: self seasideByteArray readStream. - self assert: stream next = $S. - self assert: (stream next: 1) = 'e'] - ] - - testNullCodec [ - - | codec readStream writeStream strings | - codec := GRNullCodec new. - readStream := self latin1String readStream. - writeStream := WriteStream on: String new. - strings := (OrderedCollection new) - add: self latin1String; - add: self utf8String; - add: self utf16leString; - add: self utf16beString; - add: self macromanString; - yourself. - strings do: - [:string | - self assert: (codec encode: string) = string. - self assert: (codec url encode: string) = string. - self assert: (codec decode: string) = string. - self assert: (codec url decode: string) = string]. - strings do: - [:string | - | binary encoded | - binary := string asByteArray. - encoded := (codec encoderFor: (WriteStream on: String new)) - binary; - nextPutAll: binary; - contents. - self assert: encoded = string. - encoded := (codec url encoderFor: (WriteStream on: String new)) - binary; - nextPutAll: binary; - contents. - self assert: encoded = string] - ] - - asString: aCollectionOfIntegers [ - - ^String streamContents: - [:stream | - aCollectionOfIntegers - do: [:each | stream nextPut: (Character value: each)]] - ] - - seasideByteArray [ - - ^#(83 101 97 115 105 100 101) asByteArray "Seaside" - ] -] diff --git a/grease/Tests/Core/GRCollectionTest.st b/grease/Tests/Core/GRCollectionTest.st deleted file mode 100644 index 550fea7..0000000 --- a/grease/Tests/Core/GRCollectionTest.st +++ /dev/null @@ -1,291 +0,0 @@ -TestCase subclass: GRCollectionTest [ - - - - - GRCollectionTest class >> isAbstract [ - - ^self name = #GRCollectionTest - ] - - allowsDuplicateValues [ - "Does the tested collection allow storage of duplicate (equal) values." - - - self subclassResponsibility - ] - - arbitraryCollection [ - "An general collection for testing. It should meet the needs of #duplicateElement, - #excludedElement, #includedElement, and so on where appropriate." - - - ^self collectionClass withAll: #(3 1 2 1 4) - ] - - collectionClass [ - "Answer the collection class that is being tested." - - - self subclassResponsibility - ] - - duplicateElement [ - "Answer an element that appears multiple times in #arbitraryCollection." - - - ^1 - ] - - emptyCollection [ - "Answer an empty collection." - - - ^self collectionClass new - ] - - excludedElement [ - "Answer an element that does not appear in #arbitraryCollection." - - - ^19 - ] - - includedElement [ - "Answer a (non-duplicate) element that does appear in #arbitraryCollection." - - - ^2 - ] - - isValidNewSequencedResponseClass: aClass [ - "Answer whether aClass is a valid return type for methods that return a new sequenced - collection. These are methods such as #copyFrom:to: or #reversed, which are - defined by ANSI for most classes to return the same class as the receiver. - For Interval (and may other cases), however, ANSI specifies that the response - may be any - ^self isSequencedReadable - ifTrue: - [aClass == self collectionClass - or: [aClass allSuperclasses includes: self collectionClass]] - ifFalse: [aClass == Array or: [aClass allSuperclasses includes: Array]] - ] - - assert: aCollection sortedWith: sortBlock [ - "Assert that aCollection is correctly sorted according to sortBlock." - - - 1 to: aCollection size - 1 - do: - [:index | - | a b | - a := aCollection at: index. - b := aCollection at: index + 1. - self assert: ((sortBlock value: a value: b) - or: [(sortBlock value: b value: a) not])] - ] - - assert: responseCollection validSequencedNewResponseFrom: receiverCollection [ - "Assert that the returned object is, in fact a new object, and that it is - of a valid response class for the tested collection." - - - self deny: responseCollection == receiverCollection. - self - assert: (self isValidNewSequencedResponseClass: responseCollection class) - ] - - isExtensible [ - "Answer whether the tested Collection implements the - protocol as defined in ANSI 5.7.5 ." - - - self subclassResponsibility - ] - - isInitializable [ - "Answer whether the tested Collection implements the - protocol as defined in ANSI 5.7.23." - - - self subclassResponsibility - ] - - isSequenced [ - "Answer whether the tested Collection implements the - protocol as defined in ANSI 5.7.12." - - - self subclassResponsibility - ] - - isSequencedReadable [ - "Answer whether the tested Collection implements the - protocol as defined in ANSI 5.7.8." - - - self subclassResponsibility - ] - - testAddFirst [ - - | collection | - (self isExtensible and: [self isSequenced]) ifFalse: [^self]. - collection := self arbitraryCollection. - collection addFirst: self excludedElement. - self assert: (collection at: 1) = self excludedElement. - self assert: (collection copyFrom: 2 to: collection size) - = self arbitraryCollection - ] - - testAny [ - - | collection | - collection := self arbitraryCollection. - self assert: ((self valuesOf: collection) includes: collection any) - ] - - testCopyUpTo [ - - | collection sub | - self isSequencedReadable ifFalse: [^self]. - - "match first element" - collection := self arbitraryCollection. - sub := collection copyUpTo: (collection at: 1). - self assert: sub validSequencedNewResponseFrom: collection. - self assert: sub isEmpty. - - "no match" - sub := collection copyUpTo: self excludedElement. - self assert: sub validSequencedNewResponseFrom: collection. - self assert: sub size = collection size. - self assert: sub = collection. - - "match an element" - sub := collection copyUpTo: self includedElement. - self assert: sub validSequencedNewResponseFrom: collection. - self assert: sub = (collection copyFrom: 1 to: sub size). - self assert: (collection at: sub size + 1) = self includedElement. - self allowsDuplicateValues - ifTrue: - [sub := collection copyUpTo: self duplicateElement. - self assert: sub validSequencedNewResponseFrom: collection. - self assert: sub = (collection copyFrom: 1 to: sub size). - self assert: (collection at: sub size + 1) = self duplicateElement. - self deny: (sub includes: self duplicateElement)]. - - "Make sure we're using equality" - self isInitializable - ifTrue: - [collection := self collectionClass withAll: #(1 '1'). - sub := collection copyUpTo: '1'. - self assert: sub size = 1. - self assert: (sub at: 1) = 1] - ] - - testCopyUpToLast [ - - | collection sub | - self isSequencedReadable ifFalse: [^self]. - - "match first element" - collection := self arbitraryCollection. - sub := collection copyUpToLast: collection first. - self assert: sub validSequencedNewResponseFrom: collection. - self assert: sub isEmpty. - - "no match" - sub := collection copyUpToLast: self excludedElement. - self assert: sub validSequencedNewResponseFrom: collection. - self assert: sub size = collection size. - self assert: sub = collection. - - "match an element" - sub := collection copyUpToLast: self includedElement. - self assert: sub validSequencedNewResponseFrom: collection. - self assert: sub = (collection copyFrom: 1 to: sub size). - self assert: (collection at: sub size + 1) = self includedElement. - self allowsDuplicateValues - ifTrue: - [sub := collection copyUpToLast: self duplicateElement. - self assert: sub validSequencedNewResponseFrom: collection. - self assert: sub = (collection copyFrom: 1 to: sub size). - self assert: (collection at: sub size + 1) = self duplicateElement. - self assert: (sub includes: self duplicateElement)]. - - "Make sure we're using equality" - self isInitializable - ifTrue: - [collection := self collectionClass withAll: #(1 '1'). - sub := collection copyUpToLast: '1'. - self assert: sub size = 1. - self assert: sub first = 1] - ] - - testEmptyAny [ - - | collection | - collection := self emptyCollection. - self should: [(self valuesOf: collection) includes: collection any] - raise: Error - ] - - testIsCollection [ - - self assert: self arbitraryCollection isCollection - ] - - testNoneSatisfy [ - - | excluded included | - excluded := self excludedElement. - self - assert: (self arbitraryCollection noneSatisfy: [:each | each = excluded]). - included := self includedElement. - self - deny: (self arbitraryCollection noneSatisfy: [:each | each = included]). - self assert: (self emptyCollection noneSatisfy: [:each | true]) - ] - - testNotEmpty [ - - self assert: self arbitraryCollection notEmpty. - self deny: self emptyCollection notEmpty. - self assert: self arbitraryCollection notEmpty. - self deny: self emptyCollection notEmpty - ] - - testSort [ - - | collection | - self isSequenced ifFalse: [^self]. - collection := self arbitraryCollection. - collection sort. - self assert: collection sortedWith: [:a :b | a <= b]. - collection sort: [:a :b | a > b]. - self assert: collection sortedWith: [:a :b | a > b] - ] - - testSorted [ - - | sorted collection | - collection := self arbitraryCollection. - sorted := collection sorted. - self assert: sorted validSequencedNewResponseFrom: collection. - self assert: sorted sortedWith: [:a :b | a <= b]. - sorted := collection sorted: [:a :b | a > b]. - self assert: sorted validSequencedNewResponseFrom: collection. - self assert: sorted sortedWith: [:a :b | a > b] - ] - - valuesOf: aCollection [ - "Answer the values of aCollecion. Dictionary tests override this." - - - ^aCollection - ] -] - diff --git a/grease/Tests/Core/GRDelayedSendTest.st b/grease/Tests/Core/GRDelayedSendTest.st deleted file mode 100644 index 45d2125..0000000 --- a/grease/Tests/Core/GRDelayedSendTest.st +++ /dev/null @@ -1,322 +0,0 @@ -TestCase subclass: GRDelayedSendTest [ - - - - - testArgumentCount [ - "unary" - - - | send | - send := GRDelayedSend receiver: 1 selector: #negated. - self assert: send argumentCount = 0. - send := GRDelayedSend - receiver: 1 - selector: #negated - arguments: #(). - self assert: send argumentCount = 0. - - "binary" - send := GRDelayedSend receiver: 1 selector: #+. - self assert: send argumentCount = 1. - send := GRDelayedSend - receiver: 1 - selector: #+ - argument: 2. - self assert: send argumentCount = 0. - - "keyword" - send := GRDelayedSend receiver: 1 selector: #between:and:. - self assert: send argumentCount = 2. - send := GRDelayedSend - receiver: 1 - selector: #between:and: - argument: 2. - self assert: send argumentCount = 1. - send := GRDelayedSend - receiver: 1 - selector: #between:and: - arguments: (Array with: 2 with: 3). - self assert: send argumentCount = 0 - ] - - testFixCallbackTemps [ - - | send | - send := GRDelayedSend receiver: 1 selector: #+. - self assert: send fixCallbackTemps == send. - send := GRDelayedSend - receiver: 1 - selector: #+ - argument: 2. - self assert: send fixCallbackTemps == send - ] - - testValueBinary [ - - | send | - send := GRDelayedSend receiver: 1 selector: #+. - self should: [send value] raise: GRInvalidArgumentCount. - send := GRDelayedSend - receiver: 1 - selector: #+ - argument: 2. - self assert: send value = 3 - ] - - testValueKeyword [ - - | send | - send := GRDelayedSend receiver: 1 selector: #between:and:. - self should: [send value] raise: GRInvalidArgumentCount. - send := GRDelayedSend - receiver: 1 - selector: #between:and: - argument: 2. - self should: [send value] raise: GRInvalidArgumentCount. - send := GRDelayedSend - receiver: 1 - selector: #between:and: - arguments: (Array with: 2 with: 3). - self deny: send value - ] - - testValueUnary [ - - | send | - send := GRDelayedSend receiver: 1 selector: #negated. - self assert: send value = -1. - send := GRDelayedSend - receiver: 1 - selector: #negated - arguments: #(). - self assert: send value = -1 - ] - - testValueValueBinary [ - - | send | - send := GRDelayedSend receiver: 1 selector: #+. - self should: [send value: 2 value: 3] raise: GRInvalidArgumentCount. - send := GRDelayedSend - receiver: 1 - selector: #+ - argument: 2. - self should: [send value: 2 value: 3] raise: GRInvalidArgumentCount - ] - - testValueValueKeyword [ - - | send | - send := GRDelayedSend receiver: 1 selector: #between:and:. - self deny: (send value: 2 value: 3). - send := GRDelayedSend - receiver: 1 - selector: #between:and: - argument: 2. - self should: [send value: 4 value: 5] raise: GRInvalidArgumentCount. - send := GRDelayedSend - receiver: 1 - selector: #between:and: - arguments: (Array with: 2 with: 3). - self should: [send value: 4 value: 5] raise: GRInvalidArgumentCount - ] - - testValueValueUnary [ - - | send | - send := GRDelayedSend receiver: 1 selector: #negated. - self should: [send value: 2 value: 3] raise: GRInvalidArgumentCount. - send := GRDelayedSend - receiver: 1 - selector: #negated - arguments: #(). - self should: [send value: 2 value: 3] raise: GRInvalidArgumentCount - ] - - testValueWithArgumentBinary [ - - | send | - send := GRDelayedSend receiver: 1 selector: #+. - self assert: (send value: 2) = 3. - send := GRDelayedSend - receiver: 1 - selector: #+ - argument: 2. - self should: [send value: 2] raise: GRInvalidArgumentCount - ] - - testValueWithArgumentKeyword [ - - | send | - send := GRDelayedSend receiver: 1 selector: #between:and:. - self should: [send value: 2] raise: GRInvalidArgumentCount. - send := GRDelayedSend - receiver: 1 - selector: #between:and: - argument: 2. - self deny: (send value: 3). - send := GRDelayedSend - receiver: 1 - selector: #between:and: - arguments: #(2 3). - self should: [send value: 4] raise: GRInvalidArgumentCount - ] - - testValueWithArgumentUnary [ - - | send | - send := GRDelayedSend receiver: 1 selector: #negated. - self should: [send value: 2] raise: GRInvalidArgumentCount. - send := GRDelayedSend - receiver: 1 - selector: #negated - arguments: #(). - self should: [send value: 2] raise: GRInvalidArgumentCount - ] - - testValueWithArgumentsBinary [ - - | send | - send := GRDelayedSend receiver: 1 selector: #+. - self should: [send valueWithArguments: #(2 3)] - raise: GRInvalidArgumentCount. - send := GRDelayedSend - receiver: 1 - selector: #+ - argument: 2. - self should: [send valueWithArguments: #(3 4)] - raise: GRInvalidArgumentCount - ] - - testValueWithArgumentsKeyword [ - - | send | - send := GRDelayedSend receiver: 1 selector: #between:and:. - self deny: (send valueWithArguments: #(2 3)). - send := GRDelayedSend - receiver: 1 - selector: #between:and: - argument: 2. - self should: [send valueWithArguments: #(3 4)] - raise: GRInvalidArgumentCount. - send := GRDelayedSend - receiver: 1 - selector: #between:and: - arguments: #(2 3). - self should: [send valueWithArguments: #(4 5)] - raise: GRInvalidArgumentCount - ] - - testValueWithArgumentsUnary [ - - | send | - send := GRDelayedSend receiver: 1 selector: #negated. - self should: [send valueWithArguments: #(2 3)] - raise: GRInvalidArgumentCount. - send := GRDelayedSend - receiver: 1 - selector: #negated - arguments: #(). - self should: [send valueWithArguments: #(2 3)] - raise: GRInvalidArgumentCount - ] - - testValueWithPossibleArgumentsBinary [ - - | send | - send := GRDelayedSend receiver: 1 selector: #+. - self should: [send valueWithPossibleArguments: #()] - raise: GRInvalidArgumentCount. - send := GRDelayedSend - receiver: 1 - selector: #+ - argument: 2. - self assert: (send valueWithPossibleArguments: #()) = 3. - send := GRDelayedSend receiver: 1 selector: #+. - self assert: (send valueWithPossibleArguments: #(2)) = 3. - send := GRDelayedSend - receiver: 1 - selector: #+ - argument: 2. - self assert: (send valueWithPossibleArguments: #(3)) = 3. - send := GRDelayedSend receiver: 1 selector: #+. - self assert: (send valueWithPossibleArguments: #(2 3)) = 3. - send := GRDelayedSend - receiver: 1 - selector: #+ - argument: 2. - self assert: (send valueWithPossibleArguments: #(3 4)) = 3 - ] - - testValueWithPossibleArgumentsKeyword [ - - | send | - send := GRDelayedSend receiver: 1 selector: #between:and:. - self should: [send valueWithPossibleArguments: #()] - raise: GRInvalidArgumentCount. - send := GRDelayedSend - receiver: 1 - selector: #between:and: - argument: 2. - self should: [send valueWithPossibleArguments: #()] - raise: GRInvalidArgumentCount. - send := GRDelayedSend - receiver: 1 - selector: #between:and: - arguments: (Array with: 2 with: 3). - self deny: (send valueWithPossibleArguments: #()). - send := GRDelayedSend receiver: 1 selector: #between:and:. - self should: [send valueWithPossibleArguments: #(2)] - raise: GRInvalidArgumentCount. - send := GRDelayedSend - receiver: 1 - selector: #between:and: - argument: 2. - self deny: (send valueWithPossibleArguments: #(3)). - send := GRDelayedSend - receiver: 1 - selector: #between:and: - arguments: (Array with: 2 with: 3). - self deny: (send valueWithPossibleArguments: #(4)). - send := GRDelayedSend receiver: 1 selector: #between:and:. - self deny: (send valueWithPossibleArguments: #(2 3)). - send := GRDelayedSend - receiver: 1 - selector: #between:and: - argument: 2. - self deny: (send valueWithPossibleArguments: #(3 4)). - send := GRDelayedSend - receiver: 1 - selector: #between:and: - arguments: (Array with: 2 with: 3). - self deny: (send valueWithPossibleArguments: #(4 5)) - ] - - testValueWithPossibleArgumentsUnary [ - - | send | - send := GRDelayedSend receiver: 1 selector: #negated. - self assert: (send valueWithPossibleArguments: #()) = -1. - send := GRDelayedSend - receiver: 1 - selector: #negated - arguments: #(). - self assert: (send valueWithPossibleArguments: #()) = -1. - send := GRDelayedSend receiver: 1 selector: #negated. - self assert: (send valueWithPossibleArguments: #(2)) = -1. - send := GRDelayedSend - receiver: 1 - selector: #negated - arguments: #(). - self assert: (send valueWithPossibleArguments: #(2)) = -1. - send := GRDelayedSend receiver: 1 selector: #negated. - self assert: (send valueWithPossibleArguments: #(2 3)) = -1. - send := GRDelayedSend - receiver: 1 - selector: #negated - arguments: #(). - self assert: (send valueWithPossibleArguments: #(2 3)) = -1 - ] -] - diff --git a/grease/Tests/Core/GRDictionaryTest.st b/grease/Tests/Core/GRDictionaryTest.st deleted file mode 100644 index 9ae6996..0000000 --- a/grease/Tests/Core/GRDictionaryTest.st +++ /dev/null @@ -1,27 +0,0 @@ -GRAbstractDictionaryTest subclass: GRDictionaryTest [ - - - - - collectionClass [ - - ^Dictionary - ] - - createArbitraryAssociations [ - - ^(OrderedCollection new) - add: #c -> 3; - add: #a -> 1; - add: #b -> 2; - add: #e -> 1; - add: #d -> 4; - yourself - ] - - isKey: anObject equivalentTo: anotherObject [ - - ^anObject = anotherObject - ] -] - diff --git a/grease/Tests/Core/GRDurationTest.st b/grease/Tests/Core/GRDurationTest.st deleted file mode 100644 index f72f607..0000000 --- a/grease/Tests/Core/GRDurationTest.st +++ /dev/null @@ -1,133 +0,0 @@ -TestCase subclass: GRDurationTest [ - - - - - testAccessors [ - - | duration | - duration := Duration seconds: 356521. - self assert: duration days = 4. - self assert: duration hours = 3. - self assert: duration minutes = 2. - self assert: duration seconds = 1. - self assert: duration milliseconds = 0 - ] - - testBasicInstanceCreation [ - - self - assert: (Duration - days: 1 - hours: 1 - minutes: 1 - seconds: 1) asMilliseconds - = 90061000. - self assert: (Duration weeks: 1) asMilliseconds = 604800000. - self assert: (Duration days: 1) asMilliseconds = 86400000. - self assert: (Duration hours: 1) asMilliseconds = 3600000. - self assert: (Duration minutes: 1) asMilliseconds = 60000. - self assert: (Duration seconds: 1) asMilliseconds = 1000. - self assert: (Duration milliseconds: 1) asMilliseconds = 1 - ] - - testConversions [ - - | duration | - duration := Duration - days: 4 - hours: 3 - minutes: 2 - seconds: 1. - self assert: duration asSeconds = 356521. - self assert: duration asMilliseconds = 356521000. - self assert: duration negated asSeconds = -356521. - self assert: duration negated asMilliseconds = -356521000 - ] - - testMixedInstanceCreation [ - - self - assert: (Duration - days: 1 - hours: -23 - minutes: 1 - seconds: -59) asMilliseconds - = 3601000 - ] - - testNegativeInstanceCreation [ - - self - assert: (Duration - days: -1 - hours: -1 - minutes: -1 - seconds: -1) asMilliseconds - = -90061000. - self assert: (Duration weeks: -1) asMilliseconds = -604800000. - self assert: (Duration days: -1) asMilliseconds = -86400000. - self assert: (Duration hours: -1) asMilliseconds = -3600000. - self assert: (Duration minutes: -1) asMilliseconds = -60000. - self assert: (Duration seconds: -1) asMilliseconds = -1000. - self assert: (Duration milliseconds: -1) asMilliseconds = -1 - ] - - testPartialSecondsInstanceCreation [ - "ANSI 5.8.3.1 and 5.8.3.2 specify that the seconds argument can be any - Number - not just an integer as is the case for the other arguments." - - - self - assert: (Duration - days: 0 - hours: 0 - minutes: 0 - seconds: 1.5) asMilliseconds - = 1500. - self - assert: (Duration - days: 0 - hours: 0 - minutes: 0 - seconds: 3 / 2) asMilliseconds - = 1500. - self assert: (Duration seconds: 1.5) asMilliseconds = 1500. - self assert: (Duration seconds: 3 / 2) asMilliseconds = 1500 - ] - - testRolloverInstanceCreation [ - - self - assert: (Duration - days: 0 - hours: 25 - minutes: 61 - seconds: 61) asMilliseconds - = 93721000. - self assert: (Duration hours: 25) asMilliseconds = 90000000. - self assert: (Duration minutes: 61) asMilliseconds = 3660000. - self assert: (Duration seconds: 61) asMilliseconds = 61000. - self assert: (Duration milliseconds: 1001) asMilliseconds = 1001 - ] - - testZero [ - - | duration | - duration := Duration zero. - self assert: duration isZero. - self assert: duration asMilliseconds = 0. - self assert: duration = (Duration seconds: 0) - ] - - testIntegerConvenienceMethods [ - - self assert: 5 weeks = (Duration weeks: 5). - self assert: 5 days = (Duration days: 5). - self assert: 5 hours = (Duration hours: 5). - self assert: 5 minutes = (Duration minutes: 5). - self assert: 5 seconds = (Duration seconds: 5). - self assert: 5 milliseconds = (Duration milliseconds: 5) - ] -] - diff --git a/grease/Tests/Core/GRErrorStub.st b/grease/Tests/Core/GRErrorStub.st deleted file mode 100644 index 51ed5e2..0000000 --- a/grease/Tests/Core/GRErrorStub.st +++ /dev/null @@ -1,17 +0,0 @@ -GRError subclass: GRErrorStub [ - | foo | - - - - - initialize [ - - super initialize. - foo := true - ] - - foo [ - - ^foo - ] -] diff --git a/grease/Tests/Core/GRExceptionTest.st b/grease/Tests/Core/GRExceptionTest.st deleted file mode 100644 index 2e93d63..0000000 --- a/grease/Tests/Core/GRExceptionTest.st +++ /dev/null @@ -1,207 +0,0 @@ -TestCase subclass: GRExceptionTest [ - - - - - testDefaultActionResume [ - "According to ANSI 5.5.15.2, the result of #defaultAction - should be used to resume resumable exceptions. Behaviour is undefined - for non-resumable exceptions so we do not test for that case." - - - | result | - result := GRNotificationStub signal. - self assert: result = #returnValue - ] - - testDeprecatedApi [ - - | exception seen | - exception := seen := nil. - - [self greaseDeprecatedApi: 'GRExceptionTest>>#testDeprecatedApi' - details: 'Message in a bottle.'. - seen := true] - on: GRDeprecatedApiNotification - do: - [:notification | - exception := notification. - exception resume. - seen := false]. - self assert: seen. - self assert: exception notNil. - self assert: exception messageText = 'GRExceptionTest>>#testDeprecatedApi'. - self assert: exception details = 'Message in a bottle.' - ] - - testErrorInitialization [ - "Make sure #initialize is called on #new and that calling 'super initialize' doesn't error." - - - self assert: GRErrorStub new foo - ] - - testIsResumable [ - "Make sure the platform class provides #isResumable on Exception. - This test made a bit more complex by James Foster per issue #259 - for GemStone portability." - - - | exception | - [Exception signal] on: Exception - do: - [:ex | - exception := ex. - ex return]. - self shouldnt: [exception isResumable] raise: MessageNotUnderstood - ] - - testNotificationInitialization [ - "Make sure #initialize is called on #new and that calling 'super initialize' doesn't error." - - - self assert: GRNotificationStub new foo - ] - - testOnDoImplicitReturn [ - "According to ANSI 5.5.15.2, an exception handler block that runs to completion - should result in the call to #on:do: returning the block's value." - - - | result | - result := [GRErrorStub signal] on: GRErrorStub do: [:e | #blockValue]. - self assert: result = #blockValue. - result := nil. - result := [GRNotificationStub signal] on: GRNotificationStub - do: [:e | #blockValue]. - self assert: result = #blockValue - ] - - testOnDoNonLocalReturn [ - "You should be able to do a non-local return from within an exception - handler block. We rely on a helper method here so we can check the return - value." - - - self assert: (self onExceptionReturn: 123) == 123 - ] - - testSignalError [ - "Exception>>signal is part of the ANSI Smalltalk standard. However, Seaside - only signals subclasses of WAPlatformError and WAPlatformNotification so Smalltalk - implementations that do not otherwise provide it can implement it on - these two classes." - - - [GRError new signal] on: GRError do: [:e | ^self]. - self assert: false - ] - - testSignalErrorClassSide [ - "Exception class>>signal is part of the ANSI Smalltalk standard. However, Seaside - only signals subclasses of WAPlatformError and WAPlatformNotification so Smalltalk - implementations that do not otherwise provide it can implement it on - these two classes." - - - [GRError signal] on: GRError do: [:e | ^self]. - self assert: false - ] - - testSignalNotification [ - "Exception>>signal is part of the ANSI Smalltalk standard. However, Seaside - only signals subclasses of WAPlatformError and WAPlatformNotification so Smalltalk - implementations that do not otherwise provide it can implement it on - these two classes." - - - [GRNotification new signal] on: GRNotification do: [:e | ^self]. - self assert: false - ] - - testSignalNotificationClassSide [ - "Exception class>>signal is part of the ANSI Smalltalk standard. However, Seaside - only signals subclasses of WAPlatformError and WAPlatformNotification so Smalltalk - implementations that do not otherwise provide it can implement it on - these two classes." - - - [GRNotification signal] on: GRNotification do: [:e | ^self]. - self assert: false - ] - - testSignalWithError [ - "Exception>>signal: is part of the ANSI Smalltalk standard. However, Seaside - only signals subclasses of WAPlatformError and WAPlatformNotification so Smalltalk - implementations that do not otherwise provide it can implement it on - these two classes." - - - | text | - text := 'Error!'. - [GRError new signal: text] on: GRError - do: - [:e | - self assert: e messageText = text. - ^self]. - self assert: false - ] - - testSignalWithErrorClassSide [ - "Exception class>>signal: is part of the ANSI Smalltalk standard. However, Seaside - only signals subclasses of WAPlatformError and WAPlatformNotification so Smalltalk - implementations that do not otherwise provide it can implement it on - these two classes." - - - | text | - text := 'Error!'. - [GRError signal: text] on: GRError - do: - [:e | - self assert: e messageText = text. - ^self]. - self assert: false - ] - - testSignalWithNotification [ - "Exception>>signal: is part of the ANSI Smalltalk standard. However, Seaside - only signals subclasses of WAPlatformError and WAPlatformNotification so Smalltalk - implementations that do not otherwise provide it can implement it on - these two classes." - - - | text | - text := 'Notification'. - [GRNotification new signal: text] on: GRNotification - do: - [:e | - self assert: e messageText = text. - ^self]. - self assert: false - ] - - testSignalWithNotificationClassSide [ - "Exception class>>signal: is part of the ANSI Smalltalk standard. However, Seaside - only signals subclasses of WAPlatformError and WAPlatformNotification so Smalltalk - implementations that do not otherwise provide it can implement it on - these two classes." - - - | text | - text := 'Notification'. - [GRNotification signal: text] on: GRNotification - do: - [:e | - self assert: e messageText = text. - ^self]. - self assert: false - ] - - onExceptionReturn: anObject [ - - [GRError signal] on: GRError do: [:ex | ^anObject]. - ^self - ] -] - diff --git a/grease/Tests/Core/GRIdentityDictionaryTest.st b/grease/Tests/Core/GRIdentityDictionaryTest.st deleted file mode 100644 index 795fb67..0000000 --- a/grease/Tests/Core/GRIdentityDictionaryTest.st +++ /dev/null @@ -1,27 +0,0 @@ -GRAbstractDictionaryTest subclass: GRIdentityDictionaryTest [ - - - - - collectionClass [ - - ^IdentityDictionary - ] - - createArbitraryAssociations [ - - ^(OrderedCollection new) - add: 'c' -> 3; - add: 'a' -> 1; - add: 'b' -> 2; - add: 'd' -> 1; - add: 'b' copy -> 4; - yourself - ] - - isKey: anObject equivalentTo: anotherObject [ - - ^anObject == anotherObject - ] -] - diff --git a/grease/Tests/Core/GRIntervalTest.st b/grease/Tests/Core/GRIntervalTest.st deleted file mode 100644 index 43ee55b..0000000 --- a/grease/Tests/Core/GRIntervalTest.st +++ /dev/null @@ -1,52 +0,0 @@ -GRCollectionTest subclass: GRIntervalTest [ - - - - - allowsDuplicateValues [ - - ^false - ] - - arbitraryCollection [ - - ^1 to: 4 - ] - - collectionClass [ - - ^Interval - ] - - emptyCollection [ - - ^1 to: 0 - ] - - isValidNewSequencedResponseClass: aClass [ - - ^aClass == SequenceableCollection - or: [aClass allSuperclasses includes: SequenceableCollection] - ] - - isExtensible [ - - ^false - ] - - isInitializable [ - - ^false - ] - - isSequenced [ - - ^false - ] - - isSequencedReadable [ - - ^true - ] -] - diff --git a/grease/Tests/Core/GRNotificationStub.st b/grease/Tests/Core/GRNotificationStub.st deleted file mode 100644 index 87ef9ca..0000000 --- a/grease/Tests/Core/GRNotificationStub.st +++ /dev/null @@ -1,23 +0,0 @@ -GRNotification subclass: GRNotificationStub [ - | foo | - - - - - defaultAction [ - - ^#returnValue - ] - - foo [ - - ^foo - ] - - initialize [ - - super initialize. - foo := true - ] -] - diff --git a/grease/Tests/Core/GRNullCodecStreamTest.st b/grease/Tests/Core/GRNullCodecStreamTest.st deleted file mode 100644 index 8b1098a..0000000 --- a/grease/Tests/Core/GRNullCodecStreamTest.st +++ /dev/null @@ -1,100 +0,0 @@ -TestCase subclass: GRNullCodecStreamTest [ - - - - - codecStreamClass [ - - ^GRNullCodecStream - ] - - seasideByteArray [ - - ^#(83 101 97 115 105 100 101) asByteArray "Seaside" - ] - - testCrlf [ - - | stream | - stream := GRNullCodec new encoderFor: (WriteStream on: String new). - stream crlf. - self assert: stream contents size = 2. - self assert: stream contents first = Character cr. - self assert: stream contents last = Character lf - ] - - testSpace [ - - | stream | - stream := GRNullCodec new encoderFor: (WriteStream on: String new). - stream space. - self assert: stream contents size = 1. - self assert: stream contents first = Character space - ] - - testTab [ - - | stream | - stream := GRNullCodec new encoderFor: (WriteStream on: String new). - stream tab. - self assert: stream contents size = 1. - self assert: stream contents first = Character tab - ] - - testFlush [ - - | stream | - stream := GRNullCodec new encoderFor: (WriteStream on: String new). - stream nextPutAll: 'abc'. - self shouldnt: [stream flush] raise: Error. - self assert: stream contents = 'abc' - ] - - testNext [ - - | stream | - stream := GRNullCodec new encoderFor: 'Seaside' readStream. - self assert: stream next = $S. - self assert: (stream next: 1) = 'e' - ] - - testSize [ - - | stream | - stream := GRNullCodec new encoderFor: (WriteStream on: String new). - stream nextPutAll: 'abc'. - self assert: stream size = 3. - stream nextPut: $d. - self assert: stream size = 4 - ] - - testText [ - - | stream | - stream := GRNullCodec new encoderFor: (WriteStream on: String new). - self shouldnt: [stream text] raise: Error - ] - - testReadString [ - - | stream codecStream | - stream := 'abc' readStream. - codecStream := GRNullCodec new decoderFor: stream. - self assert: codecStream next = $a. - self assert: (codecStream next: 2) = 'bc' - ] - - testWriteString [ - - | stream codecStream | - stream := WriteStream on: String new. - codecStream := GRNullCodec new encoderFor: stream. - codecStream - nextPut: $A; - nextPutAll: 'BC'; - nextPut: 68; - nextPutAll: #(69 70) asByteArray. - self assert: codecStream contents = 'ABCDEF' - ] -] - diff --git a/grease/Tests/Core/GRNumberTest.st b/grease/Tests/Core/GRNumberTest.st deleted file mode 100644 index 11a34a1..0000000 --- a/grease/Tests/Core/GRNumberTest.st +++ /dev/null @@ -1,107 +0,0 @@ -TestCase subclass: GRNumberTest [ - - - - - testBetweenAnd [ - - self assert: (6 between: 1 and: 12) - ] - - testPluralize [ - - self assert: (0 pluralize: 'person') = '0 people'. - self assert: (1 pluralize: 'person') = '1 person'. - self assert: (2 pluralize: 'person') = '2 people'. - self assert: (3 pluralize: 'person') = '3 people'. - - self assert: (0 pluralize: 'penis') = '0 penises'. - self assert: (1 pluralize: 'penis') = '1 penis'. - self assert: (2 pluralize: 'penis') = '2 penises'. - - self assert: (0 pluralize: 'person' with: 'members') = '0 members'. - self assert: (1 pluralize: 'person' with: 'members') = '1 person'. - self assert: (2 pluralize: 'person' with: 'members') = '2 members'. - self assert: (3 pluralize: 'person' with: 'members') = '3 members'. - ] - - testReadFrom [ - "We test #readFrom: as the expected behaviour on all platforms, as we - rely on it for WANumberAttribute and WAQualifiedValue" - - - self assert: (Number readFrom: '123' readStream) = 123. - - self assert: (Float readFrom: '123.45' readStream) = 123.45. - - self assert: (Number readFrom: '123.45' readStream) = 123.45. - - "This final test may not be correct. This is the expected behaviour - in Pharo. VisualWorks & GemStone64" - - self assert: (Number readFrom: 'seaside' readStream) = 0. - self assert: (Float readFrom: 'seaside' readStream) = 0.0. - ] - - testTo [ - - | collection | - collection := OrderedCollection new. - (1 to: 5) do: [:ea | collection add: ea]. - self assert: collection asArray = #(1 2 3 4 5). - - collection := OrderedCollection new. - (4 to: 4) do: [:ea | collection add: ea]. - self assert: collection asArray = #(4). - - collection := OrderedCollection new. - (5 to: 4) do: [:ea | collection add: ea]. - self assert: collection asArray = #(). - - collection := OrderedCollection new. - (-3 to: -1.5) do: [:ea | collection add: ea]. - self assert: collection asArray = #(-3 -2). - - collection := OrderedCollection new. - (1.5 to: 4) do: [:ea | collection add: ea]. - self assert: collection asArray = #(1.5 2.5 3.5) - ] - - testToDo [ - - | collection | - collection := OrderedCollection new. - 1 to: 5 do: [:ea | collection add: ea]. - self assert: collection asArray = #(1 2 3 4 5). - - collection := OrderedCollection new. - 4 to: 4 do: [:ea | collection add: ea]. - self assert: collection asArray = #(4). - - collection := OrderedCollection new. - 5 to: 4 do: [:ea | collection add: ea]. - self assert: collection asArray = #(). - - collection := OrderedCollection new. - -3 to: -1.5 do: [:ea | collection add: ea]. - self assert: collection asArray = #(-3 -2). - - collection := OrderedCollection new. - 1.5 to: 4 do: [:ea | collection add: ea]. - self assert: collection asArray = #(1.5 2.5 3.5) - ] - - testToDoClosures [ - "#to:do: may be optimized and VAST currently has problems with closures - in this case. We would prefer to use the optimized version than than - (1 to: 5) do: [ ... ] so this test is here to hilight the problem at - least unless the platforms tell us the problem is not fixable." - - - | collection | - collection := OrderedCollection new. - 1 to: 5 do: [:ea | collection add: [ea] fixCallbackTemps]. - self assert: (collection collect: [:ea | ea value]) asArray = #(1 2 3 4 5) - ] -] - diff --git a/grease/Tests/Core/GRObjectStub.st b/grease/Tests/Core/GRObjectStub.st deleted file mode 100644 index e1dad62..0000000 --- a/grease/Tests/Core/GRObjectStub.st +++ /dev/null @@ -1,18 +0,0 @@ -GRObject subclass: GRObjectStub [ - | foo | - - - - - foo [ - - ^foo - ] - - initialize [ - - super initialize. - foo := true - ] -] - diff --git a/grease/Tests/Core/GRObjectTest.st b/grease/Tests/Core/GRObjectTest.st deleted file mode 100644 index df52095..0000000 --- a/grease/Tests/Core/GRObjectTest.st +++ /dev/null @@ -1,22 +0,0 @@ -TestCase subclass: GRObjectTest [ - - - - - testError [ - "Make sure #error: signals a subclass of WAPlatformError." - - - self should: [GRObject new error: 'oh dear'] raise: GRError. - self should: [GRObject error: 'oh dear'] raise: GRError - ] - - testInitialize [ - "Make sure #initialize is called on #new and that calling - 'super initialize' doesn't error." - - - self assert: GRObjectStub new foo - ] -] - diff --git a/grease/Tests/Core/GROrderedCollectionTest.st b/grease/Tests/Core/GROrderedCollectionTest.st deleted file mode 100644 index b79dee5..0000000 --- a/grease/Tests/Core/GROrderedCollectionTest.st +++ /dev/null @@ -1,36 +0,0 @@ -GRCollectionTest subclass: GROrderedCollectionTest [ - - - - - allowsDuplicateValues [ - - ^true - ] - - collectionClass [ - - ^OrderedCollection - ] - - isExtensible [ - - ^true - ] - - isInitializable [ - - ^true - ] - - isSequenced [ - - ^true - ] - - isSequencedReadable [ - - ^true - ] -] - diff --git a/grease/Tests/Core/GROrderedMultiMapTest.st b/grease/Tests/Core/GROrderedMultiMapTest.st deleted file mode 100644 index e6e72e5..0000000 --- a/grease/Tests/Core/GROrderedMultiMapTest.st +++ /dev/null @@ -1,44 +0,0 @@ -GRSmallDictionaryTest subclass: GROrderedMultiMapTest [ - - - - - GROrderedMultiMapTest class >> shouldInheritSelectors [ - - ^true - ] - - allowsDuplicateKeys [ - - ^true - ] - - collectionClass [ - - ^GROrderedMultiMap - ] - - testAllAt [ - - self assert: (collection allAt: '1') = #(). - collection at: '1' add: 'foo'. - collection at: '1' add: 'bar'. - self assert: (collection allAt: '1') = #('foo' 'bar') - ] - - testAllAtIfAbsent [ - - self assert: (collection allAt: '1' ifAbsent: ['absent']) = 'absent'. - collection at: '1' add: 'foo'. - collection at: '1' add: 'bar'. - self assert: (collection allAt: '1' ifAbsent: ['absent']) = #('foo' 'bar') - ] - - testAtAdd [ - - collection at: '1' add: 'foo'. - collection at: '1' add: 'bar'. - self assertAssociations: (Array with: '1' -> 'foo' with: '1' -> 'bar') - ] -] - diff --git a/grease/Tests/Core/GRPackageTest.st b/grease/Tests/Core/GRPackageTest.st deleted file mode 100644 index 081f4f7..0000000 --- a/grease/Tests/Core/GRPackageTest.st +++ /dev/null @@ -1,92 +0,0 @@ -TestCase subclass: GRPackageTest [ - | package | - - - - - setUp [ - - super setUp. - package := GRPackage new - ] - - testAllDependencies [ - - | packages | - packages := Dictionary new. - packages - at: 'Lust' - put: ((GRPackage new) - name: 'Lust'; - addDependency: 'Gluttony'; - addDependency: 'Greed'; - yourself); - at: 'Gluttony' - put: ((GRPackage new) - name: 'Gluttony'; - addDependency: 'Greed'; - yourself); - at: 'Greed' - put: ((GRPackage new) - name: 'Greed'; - yourself). - packages values do: [:each | each resolveWith: packages]. - self assert: (packages at: 'Lust') allDependencies size = 3. - self assert: (packages at: 'Gluttony') allDependencies size = 2. - self assert: (packages at: 'Greed') allDependencies size = 1 - ] - - testDependencies [ - - self assert: package dependencies isEmpty. - package addDependency: 'Lust'. - package addDependency: 'Envy'. - self assert: package dependencies size = 2. - self assert: package dependencies first = 'Lust'. - self assert: package dependencies last = 'Envy' - ] - - testDescription [ - - self assert: package description isNil. - package description: 'A hopeless pacakge'. - self assert: package description = 'A hopeless pacakge' - ] - - testLicense [ - - self assert: package license = #MIT. - self assert: package isMIT. - package license: #LGPL. - self assert: package license = #LGPL. - self assert: package isLGPL - ] - - testName [ - - self assert: package name isNil. - package name: 'Gimme-Hope'. - self assert: package name = 'Gimme-Hope' - ] - - testUrl [ - - self assert: package url isNil. - package url: #seasideLGPLUrl. - self assert: package url = GRPackage new seasideLGPLUrl. - package url: 'http://www.seaside.st/distributions'. - self assert: package url = 'http://www.seaside.st/distributions' - ] - - testPackages [ - - | packages | - packages := GRPackage packages. - self assert: packages notEmpty. - packages do: [:each | - self assert: each name notEmpty. - self assert: each license notNil. - self assert: each url notNil] - ] -] - diff --git a/grease/Tests/Core/GRPlatformTest.st b/grease/Tests/Core/GRPlatformTest.st deleted file mode 100644 index c5fa9b2..0000000 --- a/grease/Tests/Core/GRPlatformTest.st +++ /dev/null @@ -1,939 +0,0 @@ -TestCase subclass: GRPlatformTest [ - - - - - decodeUtf8Character: aCollectionOfIntegers [ - "Decodes a collection of bytes into a single character. We have this so - we can avoid having non-ASCII characters in the source." - - - | codec toDecode decoded | - codec := GRCodec forEncoding: 'utf-8'. - toDecode := aCollectionOfIntegers asByteArray. - decoded := codec decode: toDecode. - self assert: decoded size = 1. - ^decoded at: 1 - ] - - platform [ - - ^GRPlatform current - ] - - testAsNumber [ - - self assert: 2007 asNumber = 2007. - self assert: '2007' asNumber = 2007 - ] - - testAsSeconds [ - - | duration | - duration := Duration - days: 1 - hours: 0 - minutes: 0 - seconds: 0. - self assert: duration asSeconds = 86400 - ] - - testBlockContextWithPossibleArguments [ - - | block | - block := [:x | 1 + x]. - self assert: (block valueWithPossibleArguments: (Array with: 2)) = 3. - block := [false not]. - self assert: (block valueWithPossibleArguments: (Array with: 3)) - ] - - testBlockValuableProtocol [ - - self assert: [nil] argumentCount isZero. - self assert: [:x | x] argumentCount = 1. - self assert: [:a :b | a + b] argumentCount = 2. - self shouldnt: [[nil] fixCallbackTemps] raise: Error. - self shouldnt: [[:x | x] fixCallbackTemps] raise: Error. - self shouldnt: [[:a :b | a + b] fixCallbackTemps] raise: Error - ] - - testCharacterAsUnicode [ - "test for: - Character >> #asUnicode - ^self asInteger" - - - self assert: $S asUnicode = 83 - ] - - testCharacterTo [ - - | actual expected | - actual := Array - withAll: 'abcdefghijklmnopqrstuvwxyzABCDEFGHIJKLMNOPQRSTUVWXYZ0123456789_-'. - actual := actual collect: [:each | each greaseInteger]. - expected := #(97 98 99 100 101 102 103 104 105 106 107 108 109 110 111 112 113 114 115 116 117 118 119 120 121 122 65 66 67 68 69 70 71 72 73 74 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 48 49 50 51 52 53 54 55 56 57 95 45). - self assert: actual size = expected size. - actual with: expected do: [:first :second | self assert: first = second] - ] - - testDateArithmetic [ - - | today tomorrow oneDay minusOneDay | - today := DateTime - year: 2008 - month: 9 - day: 13 - hour: 14 - minute: 32 - second: 5 - offset: Duration zero. - tomorrow := DateTime - year: 2008 - month: 9 - day: 14 - hour: 14 - minute: 32 - second: 5 - offset: Duration zero. - oneDay := Duration - days: 1 - hours: 0 - minutes: 0 - seconds: 0. - minusOneDay := Duration - days: -1 - hours: 0 - minutes: 0 - seconds: 0. - self assert: tomorrow - today = oneDay. - self assert: today - tomorrow = minusOneDay. - self assert: today + oneDay = tomorrow. - self assert: tomorrow - oneDay = today. - self assert: tomorrow + minusOneDay = today. - self assert: today - minusOneDay = tomorrow - ] - - testDaysInMonthForYear [ - - (1 to: 12) with: #(31 28 31 30 31 30 31 31 30 31 30 31) - do: - [:month :days | - self - assert: days = (Date daysInMonth: (Date nameOfMonth: month) forYear: 2007)] - ] - - testDigitValue [ - - '0123456789ABCDEFGHIJKLMNOPQRSTUVWXYZ' with: (0 to: 35) - do: [:each :expected | self assert: each digitValue = expected] - ] - - testEmptyOrNil [ - - self assert: '' isEmptyOrNil. - self assert: nil isEmptyOrNil. - self assert: Array new isEmptyOrNil. - self deny: 'Timberwolf' isEmptyOrNil - ] - - testFixCallbackTemps [ - "Make sure that #fixCallbackTemps is properly understood by block-contexts. Make sure that this is either a nop for Smalltalks with true block closures, or it properly fixes the context otherwise." - - - | array blocks values | - array := #(1 2 3). - blocks := array collect: [:each | [each] fixCallbackTemps]. - values := blocks collect: [:each | each value]. - self assert: values = array - ] - - testGreaseIntegerOnCharacter [ - "ASCII (1 byte)" - - - | oWithStroke euro manna | - self assert: $a greaseInteger = 97. - self assert: $A greaseInteger = 65. - - "Latin-1 (2 byte)" - oWithStroke := self decodeUtf8Character: #(195 152). - self assert: oWithStroke greaseInteger = 216. - - "BMP (3 byte)" - euro := self decodeUtf8Character: #(226 130 172). - self assert: euro greaseInteger = 8364. - - "SMP (4 byte)" - manna := self decodeUtf8Character: #(240 144 140 188). - self assert: manna greaseInteger = 66364 - ] - - testGreaseIntegerOnNumber [ - - self assert: 2007 greaseInteger = 2007. - self assert: 2007.0 greaseInteger = 2007. - self assert: 2007.1 greaseInteger = 2007. - self assert: 2007.9 greaseInteger = 2007 - ] - - testGreaseIntegerOnString [ - - self assert: '' greaseInteger isNil. - self assert: 'a' greaseInteger isNil. - self assert: ' 1' greaseInteger isNil. - self assert: 'a1' greaseInteger isNil. - self assert: '-' greaseInteger isNil. - self assert: '-a' greaseInteger isNil. - self assert: '0' greaseInteger = 0. - self assert: '12' greaseInteger = 12. - self assert: '123' greaseInteger = 123. - self assert: '123456789' greaseInteger = 123456789. - self assert: '-0' greaseInteger = 0. - self assert: '-12' greaseInteger = -12. - self assert: '-123.4' greaseInteger = -123. - self assert: '-123456789' greaseInteger = -123456789 - ] - - testGreaseString [ - - self assert: 'Timberwolf' greaseString = 'Timberwolf'. - self assert: #DireWolf greaseString = 'DireWolf'. - self assert: true greaseString = 'true'. - self assert: 666 greaseString = '666'. - self assert: $A greaseString = 'A'. - self assert: nil greaseString = 'nil'. - [1 / 0] on: ZeroDivide - do: [:error | self assert: error greaseString isString]. - self assert: 15.25 greaseString = '15.25'. - self assert: nil greaseString isString. - self assert: (4 @ 2) greaseString = '4@2'. - "#seasideString for a byte array should not do any decoding - this is in place to catch encoding errors early" - self assert: #(101 97) asByteArray greaseString ~= 'ea'. - self assert: #(101 97) asByteArray greaseString isString. - self assert: Object new greaseString isString - ] - - testIfNil [ - - self assert: (nil ifNil: [1]) = 1. - self assert: (1 ifNil: [2]) = 1 - ] - - testIfTrueIfFalse [ - - self assert: (false ifFalse: [#false]) = #false. - self assert: (false ifTrue: [#true]) isNil. - self assert: (true ifTrue: [#true]) = #true. - self assert: (true ifFalse: [#false]) isNil. - self assert: (true ifTrue: [#true] ifFalse: [#false]) = #true. - self assert: (false ifTrue: [#true] ifFalse: [#false]) = #false. - self assert: (true ifFalse: [#false] ifTrue: [#true]) = #true. - self assert: (false ifFalse: [#false] ifTrue: [#true]) = #false - ] - - testIsCharacter [ - - self deny: 7 isCharacter. - self assert: $7 isCharacter - ] - - testIsCollection [ - - self deny: Object new isCollection - ] - - testIsKeyword [ - - self deny: #isKeyword isKeyword. - self deny: #+ isKeyword. - self assert: #isKeyword: isKeyword. - self assert: #isKeyword:isKeyword: isKeyword - ] - - testIsUnary [ - - self assert: #isUnary isUnary. - self deny: #+ isUnary. - self deny: #isUnary: isUnary. - self deny: #isUnary:isUnary: isUnary - ] - - testLabel [ - - self assert: (self platform label isKindOf: String). - self deny: self platform label isEmpty - ] - - testNumArgs [ - - self assert: #not numArgs isZero. - self assert: #+ numArgs = 1. - self assert: #and: numArgs = 1. - self assert: #value:value: numArgs = 2 - ] - - testPrintStringLimitedTo [ - - | longString shortString | - longString := String - streamContents: [:stream | 1 to: 1000 do: [:i | stream nextPutAll: i printString]]. - "Squeak implementation adds 9 characters to limited string and VA Smalltalk adds 10, so we can't do an exact count." - self assert: longString printString size > 65. - shortString := longString printStringLimitedTo: 50. - self assert: shortString size < 65 - ] - - testSeconds [ - - self assert: Time now seconds isInteger. - self deny: Time now seconds isFraction - ] - - testSecureHashFor [ - "Make sure the platform class provides a #secureHashFor: method. The - method is called by Seaside when hashing passwords. The Squeak - implementation returns a SHA-1 hash but another equivalent hash method - could also be used." - - - | a b | - a := self platform secureHashFor: 'foobar'. - b := self platform secureHashFor: 'foobar'. - self assert: a = b - ] - - testStackDepth [ - - | stackDepth someBlock | - stackDepth := self platform stackDepth. - self assert: stackDepth isInteger. - self assert: stackDepth > 0. - someBlock := [self assert: self platform stackDepth > stackDepth]. - someBlock value. - self assert: stackDepth = self platform stackDepth - ] - - testSymbolAsMutator [ - "test for: - Symbol >> #asMutator - ^ (self copyWith: $:) asSymbol" - - - self assert: #name asMutator = #name: - ] - - testTotalSeconds [ - "Answer the total seconds since the Squeak epoch: 1 January 1901." - - - | seconds | - seconds := Time totalSeconds. - self assert: seconds isInteger. - self assert: seconds > 3421645167 - ] - - testVersion [ - - self assert: (self platform version isKindOf: GRVersion). - self assert: (self platform versionString isKindOf: String). - self deny: self platform versionString isEmpty - ] - - testRandomGenerator [ - - | generator collection | - generator := self platform newRandom. - self should: [generator nextInt: 0] raise: Error. - self assert: (generator nextInt: 1) = 1. - collection := (1 to: 200) collect: [:ea | generator nextInt: 2]. - self assert: (collection includes: 1). - self assert: (collection includes: 2). - self assert: collection asSet size = 2. - collection := 1 to: 5. - self assert: (collection includes: (generator randomFrom: collection)). - collection := -1.5 to: 3.5. - self assert: (collection includes: (generator randomFrom: collection)). - collection := #(1 2 3 4 5). - self assert: (collection includes: (generator randomFrom: collection)). - collection := #(1 2 3 4 5) asSet. - self assert: (collection includes: (generator randomFrom: collection)) - ] - - testReadStreamAtEnd [ - "ANSI 5.9.2.1" - - - | stream | - stream := '' readStream. - self assert: stream atEnd. - stream := 'a' readStream. - self deny: stream atEnd - ] - - testReadStreamContents [ - "ANSI 5.9.3.1" - - - | stream | - stream := 'abc' readStream. - self assert: stream contents = 'abc'. - stream next: 2. - self assert: stream contents = 'abc' - ] - - testReadStreamNegativeSkip [ - "ANSI does not mention negative values being used with #skip: but we - believe they work consistently. If not, we need to update our coding - conventions to make sure we never do this." - - - | stream position | - stream := 'abcd' readStream. - stream - next; - next. - position := stream position. - self assert: stream peek = $c. - stream skip: -1. - self assert: stream position = (position - 1). - self assert: stream peek = $b - ] - - testReadStreamNext [ - "ANSI 5.9.2.3" - - - | stream | - stream := 'abcd' readStream. - self assert: stream next = $a. - self assert: (stream next: 0) = ''. - self assert: (stream next: 1) = 'b'. - self assert: (stream next: 2) = 'cd' - ] - - testReadStreamPeek [ - "ANSI 5.9.2.7" - - - | stream | - stream := 'abcd' readStream. - self assert: stream peek = $a. - stream := '' readStream. - self assert: stream peek isNil - ] - - testReadStreamPosition [ - "ANSI 5.9.1.4 and 5.9.1.5" - - - | stream | - stream := 'abc' readStream. - self assert: stream position = 0. - stream next. - self assert: stream position = 1. - stream next. - self assert: stream position = 2. - stream next. - self assert: stream position = 3. - stream position: 1. - self assert: stream position = 1. - self assert: stream next = $b. - stream position: 0. - self assert: stream position = 0. - self assert: stream next = $a. - stream position: 3. - self assert: stream atEnd - ] - - testReadStreamReset [ - "ANSI 5.9.1.6" - - - | stream | - stream := 'abc' readStream. - stream next: 2. - stream reset. - self assert: stream next = $a - ] - - testReadStreamSkip [ - "ANSI 5.9.2.9" - - - | stream | - stream := 'abcd' readStream. - self assert: (stream - skip: 2; - peek) = $c - ] - - testReadStreamUpTo [ - "ANSI 5.9.2.11" - - - | stream | - stream := 'abcd' readStream. - self assert: (stream upTo: $c) = 'ab'. - self assert: stream next = $d. - stream := 'abcd' readStream. - self assert: (stream upTo: $x) = 'abcd'. - self assert: stream atEnd - ] - - testReadStreamUpToEnd [ - "Not defined by ANSI." - - - | stream | - stream := 'abcd' readStream. - self assert: stream upToEnd = 'abcd'. - self assert: stream atEnd. - self assert: stream upToEnd = ''. - self assert: stream atEnd. - stream := 'abcd' readStream. - stream upTo: $b. - self assert: stream upToEnd = 'cd'. - self assert: stream atEnd - ] - - testReadWriteStreamAtEnd [ - "ANSI 5.9.2.1" - - - | stream | - stream := GRPlatform current readWriteCharacterStream. - self assert: stream atEnd. - stream - nextPut: $a; - reset. - self deny: stream atEnd - ] - - testReadWriteStreamContents [ - "ANSI 5.9.3.1" - - - | stream | - stream := GRPlatform current readWriteCharacterStream. - stream - nextPutAll: 'abc'; - reset. - self assert: stream contents = 'abc'. - stream next: 2. - self assert: stream contents = 'abc'. - stream := GRPlatform current readWriteByteStream. - stream - nextPutAll: 'abc' asByteArray; - reset. - self assert: stream contents = 'abc' asByteArray. - stream next: 2. - self assert: stream contents = 'abc' asByteArray - ] - - testReadWriteStreamNegativeSkip [ - "ANSI does not mention negative values being used with #skip: but we - believe they work consistently. If not, we need to update our coding - conventions to make sure we never do this." - - - | stream position | - stream := GRPlatform current readWriteCharacterStream. - stream - nextPutAll: 'abcd'; - reset. - stream - next; - next. - position := stream position. - self assert: stream peek = $c. - stream skip: -1. - self assert: stream position = (position - 1). - self assert: stream peek = $b. - stream := GRPlatform current readWriteByteStream. - stream - nextPutAll: 'abcd' asByteArray; - reset. - stream - next; - next. - position := stream position. - self assert: stream peek = 99. - stream skip: -1. - self assert: stream position = (position - 1). - self assert: stream peek = 98 - ] - - testReadWriteStreamNext [ - "ANSI 5.9.2.3" - - - | stream | - stream := GRPlatform current readWriteCharacterStream. - stream - nextPutAll: 'abcd'; - reset. - self assert: stream next = $a. - self assert: (stream next: 0) = ''. - self assert: (stream next: 1) = 'b'. - self assert: (stream next: 2) = 'cd'. - stream := GRPlatform current readWriteByteStream. - stream - nextPutAll: 'abcd' asByteArray; - reset. - self assert: stream next = 97. - self assert: (stream next: 0) = '' asByteArray. - self assert: (stream next: 1) = 'b' asByteArray. - self assert: (stream next: 2) = 'cd' asByteArray - ] - - testReadWriteStreamNextPut [ - "ANSI 5.9.4.3" - - - | stream | - stream := GRPlatform current readWriteCharacterStream. - stream nextPut: $a. - self assert: stream contents = 'a'. - stream := GRPlatform current readWriteByteStream. - stream nextPut: 97. - self assert: stream contents = 'a' asByteArray - ] - - testReadWriteStreamNextPutAll [ - "ANSI 5.9.4.4" - - - | stream | - stream := GRPlatform current readWriteCharacterStream. - stream nextPutAll: 'abc'. - self assert: stream contents = 'abc'. - stream := GRPlatform current readWriteCharacterStream. - stream nextPutAll: #($a $b $c). - self assert: stream contents = 'abc'. - stream := GRPlatform current readWriteByteStream. - stream nextPutAll: #(97 98 99) asByteArray. - self assert: stream contents = 'abc' asByteArray - ] - - testReadWriteStreamPeek [ - "ANSI 5.9.2.7" - - - | stream | - stream := GRPlatform current readWriteCharacterStream. - self assert: stream peek isNil. - stream := GRPlatform current readWriteCharacterStream. - stream - nextPutAll: 'abcd'; - reset. - self assert: stream peek = $a. - stream := GRPlatform current readWriteByteStream. - stream - nextPutAll: 'abcd' asByteArray; - reset. - self assert: stream peek = 97 - ] - - testReadWriteStreamPosition [ - "ANSI 5.9.1.4 and 5.9.1.5" - - - | stream | - stream := GRPlatform current readWriteCharacterStream. - stream - nextPutAll: 'abc'; - reset. - self assert: stream position = 0. - stream next. - self assert: stream position = 1. - stream next. - self assert: stream position = 2. - stream next. - self assert: stream position = 3. - stream position: 1. - self assert: stream position = 1. - self assert: stream next = $b. - stream position: 0. - self assert: stream position = 0. - self assert: stream next = $a. - stream position: 3. - self assert: stream atEnd. - stream := GRPlatform current readWriteByteStream. - stream - nextPutAll: 'abc' asByteArray; - reset. - self assert: stream position = 0. - stream next. - self assert: stream position = 1. - stream next. - self assert: stream position = 2. - stream next. - self assert: stream position = 3. - stream position: 1. - self assert: stream position = 1. - self assert: stream next = 98. - stream position: 0. - self assert: stream position = 0. - self assert: stream next = 97. - stream position: 3. - self assert: stream atEnd - ] - - testReadWriteStreamReset [ - "ANSI 5.9.1.6" - - - | stream | - stream := GRPlatform current readWriteCharacterStream. - stream - nextPutAll: 'abc'; - reset. - stream next: 2. - stream reset. - self assert: stream next = $a. - stream := GRPlatform current readWriteCharacterStream. - stream - nextPutAll: 'abc'; - reset. - stream nextPutAll: 'def'. - self assert: stream contents = 'def'. - stream := GRPlatform current readWriteByteStream. - stream - nextPutAll: 'abc' asByteArray; - reset. - stream next: 2. - stream reset. - self assert: stream next = 97 - ] - - testReadWriteStreamSkip [ - "ANSI 5.9.2.9" - - - | stream | - stream := GRPlatform current readWriteCharacterStream. - stream - nextPutAll: 'abcd'; - reset. - self assert: (stream - skip: 2; - peek) = $c. - stream := GRPlatform current readWriteByteStream. - stream - nextPutAll: 'abcd' asByteArray; - reset. - self assert: (stream - skip: 2; - peek) = 99 - ] - - testReadWriteStreamTab [ - "ANSI 5.9.4.6" - - - | stream | - stream := GRPlatform current readWriteCharacterStream. - stream tab. - self assert: stream contents first = Character tab - ] - - testReadWriteStreamUpTo [ - "ANSI 5.9.2.11" - - - | stream | - stream := GRPlatform current readWriteCharacterStream. - stream - nextPutAll: 'abcd'; - reset. - self assert: (stream upTo: $c) = 'ab'. - self assert: stream next = $d. - stream := GRPlatform current readWriteCharacterStream. - stream - nextPutAll: 'abcd'; - reset. - self assert: (stream upTo: $x) = 'abcd'. - self assert: stream atEnd. - stream := GRPlatform current readWriteByteStream. - stream - nextPutAll: 'abcd' asByteArray; - reset. - self assert: (stream upTo: 99) = #(97 98) asByteArray. - self assert: stream next = 100. - stream := GRPlatform current readWriteByteStream. - stream - nextPutAll: 'abcd' asByteArray; - reset. - self assert: (stream upTo: 120) = #(97 98 99 100) asByteArray. - self assert: stream atEnd - ] - - testReadWriteStreamUpToEnd [ - "Not defined by ANSI." - - - | stream | - stream := GRPlatform current readWriteCharacterStream. - stream - nextPutAll: 'abcd'; - reset. - self assert: stream upToEnd = 'abcd'. - self assert: stream atEnd. - self assert: stream upToEnd = ''. - self assert: stream atEnd. - stream reset. - stream upTo: $b. - self assert: stream upToEnd = 'cd'. - self assert: stream atEnd. - stream := GRPlatform current readWriteByteStream. - stream - nextPutAll: 'abcd' asByteArray; - reset. - self assert: stream upToEnd = #(97 98 99 100) asByteArray. - self assert: stream atEnd. - self assert: stream upToEnd = #() asByteArray. - self assert: stream atEnd. - stream reset. - stream upTo: 98. - self assert: stream upToEnd = #(99 100) asByteArray. - self assert: stream atEnd - ] - - testWriteStreamContents [ - "ANSI 5.9.3.1" - - - | stream | - stream := WriteStream on: String new. - stream nextPutAll: 'abc'. - self assert: stream contents = 'abc'. - stream nextPutAll: 'def'. - self assert: stream contents = 'abcdef' - ] - - testWriteStreamCrLf [ - - | stream | - stream := WriteStream on: String new. - stream crlf. - self assert: stream contents first codePoint = 13. - self assert: stream contents second codePoint = 10 - ] - - testWriteStreamNextPut [ - "ANSI 5.9.4.3" - - - | stream | - stream := WriteStream on: String new. - stream nextPut: $a. - self assert: stream contents = 'a' - ] - - testWriteStreamNextPutAll [ - "ANSI 5.9.4.4" - - - | stream | - stream := WriteStream on: String new. - stream nextPutAll: 'abc'. - self assert: stream contents = 'abc'. - stream := WriteStream on: String new. - stream nextPutAll: #($a $b $c). - self assert: stream contents = 'abc' - ] - - testWriteStreamReset [ - "ANSI 5.9.1.6" - - - | stream | - stream := WriteStream on: String new. - stream nextPutAll: 'abc'. - stream reset. - stream nextPutAll: 'def'. - self assert: stream contents = 'def' - ] - - testWriteStreamSpace [ - "ANSI 5.9.4.5" - - - | stream | - stream := WriteStream on: String new. - stream space. - self assert: stream contents first = Character space - ] - - testWriteStreamTab [ - "ANSI 5.9.4.6" - - - | stream | - stream := WriteStream on: String new. - stream tab. - self assert: stream contents first = Character tab - ] - - testReadStreamSeasideUpToAll [ - - | stream string1 string2 | - stream := 'abc12def' readStream. - string1 := stream greaseUpToAll: '12'. - string2 := stream greaseUpToAll: '12'. - self assert: string1 = 'abc'. - self assert: string2 = 'def'. - self assert: stream atEnd - ] - - testShutDownList [ - "A smoke test: checks if the test-class can be added and removed to the shutdown list." - - - [self platform addToShutDownList: self class] - ensure: [self platform removeFromShutDownList: self class] - ] - - testStartUpList [ - "A smoke test: checks if the test-class can be added and removed to the startup list." - - - [self platform addToStartUpList: self class] - ensure: [self platform removeFromStartUpList: self class] - ] - - testTerminate [ - - | ensureRun ifCurtailedRun semaphore1 semaphore2 semaphore3 semaphore4 process | - ensureRun := false. - ifCurtailedRun := false. - semaphore1 := self platform semaphoreClass new. - semaphore2 := self platform semaphoreClass new. - semaphore3 := self platform semaphoreClass new. - semaphore4 := self platform semaphoreClass new. - process := [[[semaphore1 signal. - semaphore2 wait] ensure: - [ensureRun := true. - semaphore3 signal]] - ifCurtailed: - [ifCurtailedRun := true. - semaphore4 signal]] - newProcess. - self deny: (self platform isProcessTerminated: process). - process resume. - semaphore1 wait. - self deny: (self platform isProcessTerminated: process). - self platform terminateProcess: process. - semaphore3 wait. - self assert: ensureRun. - semaphore4 wait. - self assert: ifCurtailedRun. - self assert: (self platform isProcessTerminated: process) - ] -] - diff --git a/grease/Tests/Core/GRPrinterTest.st b/grease/Tests/Core/GRPrinterTest.st deleted file mode 100644 index 8512ad0..0000000 --- a/grease/Tests/Core/GRPrinterTest.st +++ /dev/null @@ -1,805 +0,0 @@ -TestCase subclass: GRPrinterTest [ - - - - - GRPrinterTest class >> packageNamesUnderTest [ - - ^#('Grease-Core') - ] - - testComposedPrinter [ - - | converter | - converter := GRSequentialPrinter new , 'CHF ' , GRNumberPrinter new. - self assert: (converter print: 1234) = 'CHF 1234'. - self assert: (converter print: -1234) = 'CHF 1234'. - converter := GRSignPrinter new , GRNumberPrinter new , '%'. - self assert: (converter print: 1234) = '1234%'. - self assert: (converter print: -1234) = '-1234%' - ] - - testFileSizePrinterBinary [ - - | converter | - converter := GRPrinter binaryFileSize. - self assert: (converter print: 1) = '1 byte'. - self assert: (converter print: 2) = '2 bytes'. - self assert: (converter print: 30) = '30 bytes'. - self assert: (converter print: 500) = '500 bytes'. - self assert: (converter print: 6000) = '5.9 KiB'. - self assert: (converter print: 70000) = '68.4 KiB'. - self assert: (converter print: 800000) = '781.3 KiB'. - self assert: (converter print: 9000000) = '8.6 MiB'. - self assert: (converter print: 10000000) = '9.5 MiB'. - self assert: (converter print: 200000000) = '190.7 MiB'. - self assert: (converter print: 3000000000) = '2.8 GiB'. - self assert: (converter print: 40000000000) = '37.3 GiB' - ] - - testFileSizePrinterDecimal [ - - | converter | - converter := GRPrinter decimalFileSize. - self assert: (converter print: 1) = '1 byte'. - self assert: (converter print: 2) = '2 bytes'. - self assert: (converter print: 30) = '30 bytes'. - self assert: (converter print: 500) = '500 bytes'. - self assert: (converter print: 6000) = '6.0 kB'. - self assert: (converter print: 70000) = '70.0 kB'. - self assert: (converter print: 800000) = '800.0 kB'. - self assert: (converter print: 9000000) = '9.0 MB'. - self assert: (converter print: 10000000) = '10.0 MB'. - self assert: (converter print: 200000000) = '200.0 MB'. - self assert: (converter print: 3000000000) = '3.0 GB'. - self assert: (converter print: 40000000000) = '40.0 GB' - ] - - testFloatPrinter [ - - | converter | - converter := GRNumberPrinter new precision: 2. - self assert: (converter print: 1.009) = '1.01'. - self assert: (converter print: 1.01) = '1.01'. - self assert: (converter print: 1.019) = '1.02'. - self assert: (converter print: 1.25) = '1.25'. - self assert: (converter print: 1.254) = '1.25'. - self assert: (converter print: 1.256) = '1.26'. - self assert: (converter print: 1.009) = '1.01'. - self assert: (converter print: 0.9) = '0.90'. - self assert: (converter print: 0.99) = '0.99'. - self assert: (converter print: 0.999) = '1.00'. - self assert: (converter print: 0.9999) = '1.00'. - self assert: (converter print: -0.9) = '0.90'. - self assert: (converter print: -0.99) = '0.99'. - self assert: (converter print: -0.999) = '1.00'. - self assert: (converter print: -0.9999) = '1.00' - ] - - testFloatPrinterInfinity [ - - | converter | - converter := GRNumberPrinter new. - self assert: (converter print: Float infinity) = 'Infinite'. - self assert: (converter print: Float infinity negated) = 'Infinite'. - converter infinite: 'very huge'. - self assert: (converter print: Float infinity) = 'very huge'. - self assert: (converter print: Float infinity negated) = 'very huge' - ] - - testFloatPrinterNaN [ - - | converter | - converter := GRNumberPrinter new. - self assert: (converter print: Float nan) = 'NaN'. - converter nan: 'Not A Number'. - self assert: (converter print: Float nan) = 'Not A Number' - ] - - testFloatPrinterPadding [ - - | converter | - converter := GRNumberPrinter new. - converter digits: 3. - self assert: (converter print: 1) = ' 1'. - self assert: (converter print: 12) = ' 12'. - self assert: (converter print: 123) = '123'. - self assert: (converter print: 1234) = '1234'. - converter padding: $*. - self assert: (converter print: 1) = '**1'. - self assert: (converter print: 12) = '*12'. - self assert: (converter print: 123) = '123'. - self assert: (converter print: 1234) = '1234' - ] - - testFloatPrinterSeparator [ - - | converter | - converter := GRNumberPrinter new. - converter - precision: 2; - separator: $*. - self assert: (converter print: 12345.0) = '12*345.00'. - self assert: (converter print: 0.6789000000000001) = '0.68'. - converter - precision: 4; - separator: $!. - self assert: (converter print: 12345.0) = '12!345.000!0'. - self assert: (converter print: 0.6789000000000001) = '0.678!9' - ] - - testIntegerPrinter [ - - | converter | - converter := GRNumberPrinter new. - self assert: (converter print: 1234) = '1234'. - self assert: (converter print: -1234) = '1234'. - converter separator: $.. - self assert: (converter print: 1234) = '1.234'. - self assert: (converter print: 1234567) = '1.234.567'. - converter - base: 16; - separator: nil. - self assert: (converter print: 1234) = '4d2'. - self assert: (converter print: 123123) = '1e0f3'. - converter uppercase. - self assert: (converter print: 1234) = '4D2'. - self assert: (converter print: 123123) = '1E0F3' - ] - - testOrdinalizePrinter [ - - | converter | - converter := GRNumberPrinter new , GROrdinalizePrinter new. - self assert: (converter print: 1) = '1st'. - self assert: (converter print: 2) = '2nd'. - self assert: (converter print: 3) = '3rd'. - self assert: (converter print: 4) = '4th'. - self assert: (converter print: 10) = '10th'. - self assert: (converter print: 111) = '111th'. - self assert: (converter print: 212) = '212th'. - self assert: (converter print: 313) = '313th'. - self assert: (converter print: 414) = '414th'. - self assert: (converter print: 20) = '20th'. - self assert: (converter print: 121) = '121st'. - self assert: (converter print: 222) = '222nd'. - self assert: (converter print: 323) = '323rd'. - self assert: (converter print: 424) = '424th' - ] - - testSignPrinter [ - - | converter | - converter := GRSignPrinter new. - converter - negativePrinter: $-; - positivePrinter: $+. - self assert: (converter print: 12) = '+'. - self assert: (converter print: -12) = '-' - ] - - testStringPrinter [ - - | converter | - converter := GRStringPrinter new. - self assert: (converter print: 123) = '123'. - self assert: (converter print: 'foo') = 'foo'. - self assert: (converter print: true) = 'true' - ] - - testStringPrinterLength [ - - | converter | - converter := GRStringPrinter new. - self assert: (converter print: 'foo') = 'foo'. - converter length: 3. - self assert: (converter print: 'foo') = 'foo'. - converter length: 1. - self assert: (converter print: 'foo') = 'f' - ] - - testStringPrinterPad [ - - | converter | - converter := GRStringPrinter new. - converter - character: $*; - length: 5. - converter padLeft. - self assert: (converter print: 'foo') = '**foo'. - converter padRight. - self assert: (converter print: 'foo') = 'foo**'. - converter padCenter. - self assert: (converter print: 'foo') = '*foo*' - ] - - testStringPrinterTrim [ - - | converter | - converter := GRStringPrinter new. - self assert: (converter print: ' foo ') = ' foo '. - converter trimLeft. - self assert: (converter print: ' foo ') = 'foo '. - converter trimRight. - self assert: (converter print: ' foo ') = ' foo'. - converter trimBoth. - self assert: (converter print: ' foo ') = 'foo' - ] - - testCookieTimestamp [ - - | printer date | - printer := GRPrinter cookieTimestamp. - date := DateTime - year: 2008 - month: 8 - day: 1 - hour: 9 - minute: 4 - second: 4 - offset: (Duration - days: 0 - hours: 0 - minutes: 0 - seconds: 0). - self assert: (printer print: date) = 'Fri, 01-Aug-2008 09:04:04 GMT' - ] - - testHttp [ - - | printer date offsetHour | - offsetHour := 2. - printer := GRPrinter httpDate. - date := DateTime - year: 1994 - month: 11 - day: 6 - hour: 8 + offsetHour - minute: 49 - second: 37 - offset: (Duration - days: 0 - hours: offsetHour - minutes: 0 - seconds: 0). - self assert: (printer print: date) = 'Sun, 06 Nov 1994 08:49:37 GMT' - ] - - testIsoDate [ - - | printer | - printer := GRPrinter isoDate. - self - assert: (printer print: (Date - year: 1980 - month: 6 - day: 11)) - = '1980-06-11'. - self - assert: (printer print: (Date - year: 2003 - month: 12 - day: 1)) - = '2003-12-01'. - self - assert: (printer print: (Date - year: 800 - month: 12 - day: 24)) - = '0800-12-24' - ] - - testIsoTime [ - - | printer | - printer := GRPrinter isoTime. - self - assert: (printer print: (Time - hour: 0 - minute: 0 - second: 0)) - = '00:00:00'. - self - assert: (printer print: (Time - hour: 1 - minute: 2 - second: 3)) - = '01:02:03'. - self - assert: (printer print: (Time - hour: 12 - minute: 23 - second: 34)) - = '12:23:34' - ] - - testRfc822 [ - - | printer date | - printer := GRPrinter rfc822. - date := DateTime - year: 2008 - month: 8 - day: 1 - hour: 9 - minute: 4 - second: 4 - offset: (Duration - days: 0 - hours: -2 - minutes: 0 - seconds: 0). - self assert: (printer print: date) = 'Fri, 01 Aug 2008 09:04:04 -0200'. - date := DateTime - year: 2008 - month: 8 - day: 31 - hour: 19 - minute: 41 - second: 46 - offset: (Duration - days: 0 - hours: 0 - minutes: 30 - seconds: 0). - self assert: (printer print: date) = 'Sun, 31 Aug 2008 19:41:46 +0030' - ] - - testRfc822WithTimeZone [ - - | printer date | - printer := GRPrinter rfc822WithTimeZone: 'GMT'. - date := DateTime - year: 2008 - month: 8 - day: 1 - hour: 9 - minute: 4 - second: 4 - offset: (Duration - days: 0 - hours: 0 - minutes: 0 - seconds: 0). - self assert: (printer print: date) = 'Fri, 01 Aug 2008 09:04:04 GMT' - ] - - testDigitsOf [ - - | converter | - converter := GRNumberPrinter new. - self assert: (converter digitsOf: 0.0 base: 10) = '0'. - self assert: (converter digitsOf: 1.0 base: 10) = '1'. - self assert: (converter digitsOf: -1.0 base: 10) = '1'. - self assert: (converter digitsOf: -1234567890 base: 10) = '1234567890'. - self assert: (converter digitsOf: 1234567890 base: 10) = '1234567890'. - self assert: (converter digitsOf: -9876543210 base: 10) = '9876543210'. - self assert: (converter digitsOf: 9876543210 base: 10) = '9876543210' - ] - - testDigitsOfBase [ - - | converter | - converter := GRNumberPrinter new. - self assert: (converter digitsOf: 1234 base: 2) = '10011010010'. - self assert: (converter digitsOf: 1234 base: 3) = '1200201'. - self assert: (converter digitsOf: 1234 base: 4) = '103102'. - self assert: (converter digitsOf: 1234 base: 5) = '14414'. - self assert: (converter digitsOf: 1234 base: 6) = '5414'. - self assert: (converter digitsOf: 1234 base: 7) = '3412'. - self assert: (converter digitsOf: 1234 base: 8) = '2322'. - self assert: (converter digitsOf: 1234 base: 9) = '1621'. - self assert: (converter digitsOf: 1234 base: 10) = '1234'. - self assert: (converter digitsOf: 1234 base: 11) = 'a22'. - self assert: (converter digitsOf: 1234 base: 12) = '86a'. - self assert: (converter digitsOf: 1234 base: 13) = '73c'. - self assert: (converter digitsOf: 1234 base: 14) = '642'. - self assert: (converter digitsOf: 1234 base: 15) = '574'. - self assert: (converter digitsOf: 1234 base: 16) = '4d2' - ] - - testPadCenter [ - - | converter | - converter := GRPrinter new. - self - assert: (converter - pad: '' - center: $* - to: 3) = '***'. - self - assert: (converter - pad: '1' - center: $* - to: 3) = '*1*'. - self - assert: (converter - pad: '12' - center: $* - to: 3) = '12*'. - self - assert: (converter - pad: '123' - center: $* - to: 3) = '123'. - self - assert: (converter - pad: '1234' - center: $* - to: 3) = '1234' - ] - - testPadLeft [ - - | converter | - converter := GRPrinter new. - self assert: (converter - pad: '' - left: $* - to: 3) = '***'. - self - assert: (converter - pad: '1' - left: $* - to: 3) = '**1'. - self - assert: (converter - pad: '12' - left: $* - to: 3) = '*12'. - self - assert: (converter - pad: '123' - left: $* - to: 3) = '123'. - self - assert: (converter - pad: '1234' - left: $* - to: 3) = '1234' - ] - - testPadRight [ - - | converter | - converter := GRPrinter new. - self - assert: (converter - pad: '' - right: $* - to: 3) = '***'. - self - assert: (converter - pad: '1' - right: $* - to: 3) = '1**'. - self - assert: (converter - pad: '12' - right: $* - to: 3) = '12*'. - self - assert: (converter - pad: '123' - right: $* - to: 3) = '123'. - self - assert: (converter - pad: '1234' - right: $* - to: 3) = '1234' - ] - - testSeparateLeft [ - - | converter | - converter := GRNumberPrinter new. - self assert: (converter separate: '' left: $*) = ''. - self assert: (converter separate: '1' left: $*) = '1'. - self assert: (converter separate: '12' left: $*) = '12'. - self assert: (converter separate: '123' left: $*) = '123'. - self assert: (converter separate: '1234' left: $*) = '123*4'. - self assert: (converter separate: '12345' left: $*) = '123*45'. - self assert: (converter separate: '123456' left: $*) = '123*456'. - self assert: (converter separate: '1234567' left: $*) = '123*456*7'. - self assert: (converter separate: '12345678' left: $*) = '123*456*78'. - self assert: (converter separate: '123456789' left: $*) = '123*456*789' - ] - - testSeparateRight [ - - | converter | - converter := GRNumberPrinter new. - self assert: (converter separate: '' right: $*) = ''. - self assert: (converter separate: '1' right: $*) = '1'. - self assert: (converter separate: '12' right: $*) = '12'. - self assert: (converter separate: '123' right: $*) = '123'. - self assert: (converter separate: '1234' right: $*) = '1*234'. - self assert: (converter separate: '12345' right: $*) = '12*345'. - self assert: (converter separate: '123456' right: $*) = '123*456'. - self assert: (converter separate: '1234567' right: $*) = '1*234*567'. - self assert: (converter separate: '12345678' right: $*) = '12*345*678'. - self assert: (converter separate: '123456789' right: $*) = '123*456*789' - ] - - testFullMonthName [ - - | printer | - printer := GRPrinter fullMonthName. - self - assert: (printer print: (Date - year: 2000 - month: 8 - day: 1)) - = 'August'. - self - assert: (printer print: (Date - year: 2000 - month: 11 - day: 1)) - = 'November' - ] - - testFullWeekName [ - - | printer | - printer := GRPrinter fullWeekName. - self - assert: (printer print: (Date - year: 1980 - month: 1 - day: 1)) - = 'Tuesday'. - self - assert: (printer print: (Date - year: 2000 - month: 1 - day: 1)) - = 'Saturday' - ] - - testPaddedCentury [ - - | printer | - printer := GRPrinter paddedCentury. - self - assert: (printer print: (Date - year: 1980 - month: 1 - day: 1)) - = '80'. - self - assert: (printer print: (Date - year: 2009 - month: 1 - day: 1)) - = '09' - ] - - testUnpaddedCentury [ - - | printer | - printer := GRPrinter unpaddedCentury. - self - assert: (printer print: (Date - year: 1980 - month: 1 - day: 1)) - = '80'. - self - assert: (printer print: (Date - year: 2009 - month: 1 - day: 1)) - = '9' - ] - - testUnpaddedDay [ - - | printer | - printer := GRPrinter unpaddedDay. - self - assert: (printer print: (Date - year: 2000 - month: 1 - day: 4)) - = '4'. - self - assert: (printer print: (Date - year: 2000 - month: 1 - day: 19)) - = '19' - ] - - testUnpaddedMonth [ - - | printer | - printer := GRPrinter unpaddedMonth. - self - assert: (printer print: (Date - year: 2000 - month: 8 - day: 1)) - = '8'. - self - assert: (printer print: (Date - year: 2000 - month: 11 - day: 1)) - = '11' - ] - - testUnpaddedYear [ - - | printer | - printer := GRPrinter unpaddedYear. - self - assert: (printer print: (Date - year: 766 - month: 1 - day: 1)) - = '766'. - self - assert: (printer print: (Date - year: 1980 - month: 1 - day: 1)) - = '1980'. - self - assert: (printer print: (Date - year: 2009 - month: 1 - day: 1)) - = '2009' - ] - - testPaddedHour12 [ - - | printer | - printer := GRPrinter paddedHour12. - self - assert: (printer print: (Time - hour: 5 - minute: 0 - second: 0)) - = '05'. - self - assert: (printer print: (Time - hour: 10 - minute: 0 - second: 0)) - = '10'. - self - assert: (printer print: (Time - hour: 14 - minute: 0 - second: 0)) - = '02'. - self - assert: (printer print: (Time - hour: 23 - minute: 0 - second: 0)) - = '11' - ] - - testUnpaddedHour12 [ - - | printer | - printer := GRPrinter unpaddedHour12. - self - assert: (printer print: (Time - hour: 5 - minute: 0 - second: 0)) - = '5'. - self - assert: (printer print: (Time - hour: 10 - minute: 0 - second: 0)) - = '10'. - self - assert: (printer print: (Time - hour: 14 - minute: 0 - second: 0)) - = '2'. - self - assert: (printer print: (Time - hour: 23 - minute: 0 - second: 0)) - = '11' - ] - - testUnpaddedHour24 [ - - | printer | - printer := GRPrinter unpaddedHour24. - self - assert: (printer print: (Time - hour: 5 - minute: 0 - second: 0)) - = '5'. - self - assert: (printer print: (Time - hour: 10 - minute: 0 - second: 0)) - = '10'. - self - assert: (printer print: (Time - hour: 14 - minute: 0 - second: 0)) - = '14'. - self - assert: (printer print: (Time - hour: 23 - minute: 0 - second: 0)) - = '23' - ] - - testUnpaddedMinute [ - - | printer | - printer := GRPrinter unpaddedMinute. - self - assert: (printer print: (Time - hour: 0 - minute: 5 - second: 0)) - = '5'. - self - assert: (printer print: (Time - hour: 0 - minute: 12 - second: 0)) - = '12' - ] - - testUnpaddedSecond [ - - | printer | - printer := GRPrinter unpaddedSecond. - self - assert: (printer print: (Time - hour: 0 - minute: 0 - second: 0)) - = '0'. - self - assert: (printer print: (Time - hour: 0 - minute: 0 - second: 9)) - = '9'. - self - assert: (printer print: (Time - hour: 0 - minute: 0 - second: 12)) - = '12' - ] - - testSwissCurrency [ - - | printer | - printer := GRPrinter swissCurrency. - self assert: (printer print: 12.34) = 'CHF 12.35'. - self assert: (printer print: -12.39) = 'CHF -12.40' - ] - - testUsCurrency [ - - | printer | - printer := GRPrinter usCurrency. - self assert: (printer print: 12.34) = '$12.34'. - self assert: (printer print: -12.34) = '-$12.34' - ] -] - diff --git a/grease/Tests/Core/GRSetTest.st b/grease/Tests/Core/GRSetTest.st deleted file mode 100644 index b510092..0000000 --- a/grease/Tests/Core/GRSetTest.st +++ /dev/null @@ -1,36 +0,0 @@ -GRCollectionTest subclass: GRSetTest [ - - - - - allowsDuplicateValues [ - - ^false - ] - - collectionClass [ - - ^Set - ] - - isExtensible [ - - ^true - ] - - isInitializable [ - - ^true - ] - - isSequenced [ - - ^false - ] - - isSequencedReadable [ - - ^false - ] -] - diff --git a/grease/Tests/Core/GRSmallDictionaryTest.st b/grease/Tests/Core/GRSmallDictionaryTest.st deleted file mode 100644 index 5a2d169..0000000 --- a/grease/Tests/Core/GRSmallDictionaryTest.st +++ /dev/null @@ -1,321 +0,0 @@ -TestCase subclass: GRSmallDictionaryTest [ - | collection | - - - - - allowsDuplicateKeys [ - - ^false - ] - - collectionClass [ - - ^GRSmallDictionary - ] - - isKey: anObject equivalentTo: anotherObject [ - - ^anObject = anotherObject - ] - - newCollection [ - - ^self collectionClass new - ] - - assertAssociations: anOrderedCollection [ - - | associations iterated | - associations := collection associations. - iterated := Array - streamContents: [:stream | collection associationsDo: [:each | stream nextPut: each]]. - self assert: associations size = anOrderedCollection size. - self assert: iterated size = anOrderedCollection size. - 1 to: anOrderedCollection size - do: - [:index | - self assert: (associations at: index) = (anOrderedCollection at: index). - self assert: (iterated at: index) = (anOrderedCollection at: index)] - ] - - setUp [ - - super setUp. - collection := self newCollection - ] - - testAddAll [ - - | dict result | - dict := (Dictionary new) - at: '1' put: 'foo'; - yourself. - result := collection addAll: dict. - self assert: result == dict. - self assertAssociations: (Array with: '1' -> 'foo'). - dict := (GROrderedMultiMap new) - at: '1' put: 'foo'; - at: '1' add: 'bar'; - yourself. - collection := self newCollection. - result := collection addAll: dict. - self assert: result == dict. - self assertAssociations: (self allowsDuplicateKeys - ifFalse: [Array with: '1' -> 'bar'] - ifTrue: [Array with: '1' -> 'foo' with: '1' -> 'bar']) - ] - - testAddAndAssociations [ - - | association | - association := collection add: '1' -> 'foo'. - self assert: association key = '1'. - self assert: association value = 'foo'. - self assertAssociations: (Array with: '1' -> 'foo'). - association := collection add: '2' -> 'bar'. - self assert: association key = '2'. - self assert: association value = 'bar'. - self assertAssociations: (Array with: '1' -> 'foo' with: '2' -> 'bar'). - association := collection add: '1' -> 'baz'. - self assert: association key = '1'. - self assert: association value = 'baz'. - self assertAssociations: (self allowsDuplicateKeys - ifFalse: [Array with: '1' -> 'baz' with: '2' -> 'bar'] - ifTrue: - [Array - with: '1' -> 'foo' - with: '2' -> 'bar' - with: '1' -> 'baz']) - ] - - testAt [ - - self should: [collection at: '1'] raise: Error. - collection add: '1' -> 'foo'. - collection add: '1' -> 'bar'. - self assert: (collection at: '1') - = (self allowsDuplicateKeys ifTrue: ['foo'] ifFalse: ['bar']) - ] - - testAtIfAbsent [ - - self assert: (collection at: '1' ifAbsent: ['foo']) = 'foo'. - collection add: '1' -> 'bar'. - collection add: '1' -> 'baz'. - self assert: (collection at: '1' ifAbsent: ['foo']) - = (self allowsDuplicateKeys ifTrue: ['bar'] ifFalse: ['baz']) - ] - - testAtIfAbsentPut [ - - self assert: (collection at: '1' ifAbsentPut: ['foo']) = 'foo'. - self assertAssociations: (Array with: '1' -> 'foo'). - self assert: (collection at: '1' ifAbsentPut: ['bar']) = 'foo'. - self assertAssociations: (Array with: '1' -> 'foo') - ] - - testAtIfPresent [ - - collection add: '1' -> 'foo'. - collection add: '1' -> 'bar'. - self assert: (collection at: '1' ifPresent: [:v | v , 'baz']) - = (self allowsDuplicateKeys ifTrue: ['foobaz'] ifFalse: ['barbaz']). - self assert: (collection at: '2' ifPresent: [:v | v , 'baz']) isNil - ] - - testAtPut [ - - collection at: '1' put: 'foo'. - collection at: '2' put: 'bar'. - self assertAssociations: (Array with: '1' -> 'foo' with: '2' -> 'bar'). - collection at: '1' put: 'baz'. - self assertAssociations: (Array with: '1' -> 'baz' with: '2' -> 'bar') - ] - - testRemoveKey [ - - self should: [collection removeKey: '1'] raise: Error. - collection add: '1' -> 'foo'. - collection add: '1' -> 'bar'. - collection add: '2' -> 'baz'. - self assert: (collection removeKey: '1') - = (self allowsDuplicateKeys ifTrue: [#('foo' 'bar')] ifFalse: ['bar']). - self assertAssociations: (Array with: '2' -> 'baz'). - self assert: (collection removeKey: '2') - = (self allowsDuplicateKeys ifTrue: [#('baz')] ifFalse: ['baz']). - self assertAssociations: #() - ] - - testRemoveKeyIfAbsent [ - - self assert: (collection removeKey: '1' ifAbsent: ['absent']) = 'absent'. - collection add: '1' -> 'foo'. - collection add: '1' -> 'bar'. - collection add: '2' -> 'baz'. - self assert: (collection removeKey: '1' ifAbsent: ['absent']) - = (self allowsDuplicateKeys ifTrue: [#('foo' 'bar')] ifFalse: ['bar']). - self assertAssociations: (Array with: '2' -> 'baz'). - self assert: (collection removeKey: '2' ifAbsent: ['absent']) - = (self allowsDuplicateKeys ifTrue: [#('baz')] ifFalse: ['baz']). - self assertAssociations: #() - ] - - testSize [ - - self assert: collection size = 0. - collection add: '1' -> 'foo'. - self assert: collection size = 1. - collection add: '2' -> 'bar'. - self assert: collection size = 2. - collection add: '1' -> 'baz'. - self assert: collection size - = (self allowsDuplicateKeys ifTrue: [3] ifFalse: [2]) - ] - - testCopy [ - - | other | - collection - at: 1 put: 'foo'; - at: 2 put: 'bar'. - other := collection copy. - collection - at: 1 put: 'zork'; - at: 3 put: 'zonk'. - other at: 2 put: 'other'. - self assert: collection size = 3. - self assert: (collection at: 1) = 'zork'. - self assert: (collection at: 2) = 'bar'. - self assert: (collection at: 3) = 'zonk'. - self assert: other size = 2. - self assert: (other at: 1) = 'foo'. - self assert: (other at: 2) = 'other' - ] - - testGrow [ - - 1 to: 100 - do: - [:i | - collection at: i put: i negated. - self assert: collection size = i. - - [:array :factor | - self assert: array size = i. - 1 to: i do: [:j | self assert: (array at: j) = (factor * j)]] - value: collection keys value: 1; - value: collection values value: -1] - ] - - testWithAll [ - - | dict | - dict := (Dictionary new) - at: '1' put: 'foo'; - yourself. - collection := self collectionClass withAll: dict. - self assertAssociations: (Array with: '1' -> 'foo'). - dict := (GROrderedMultiMap new) - at: '1' put: 'foo'; - at: '1' add: 'bar'; - yourself. - collection := self collectionClass withAll: dict. - self assertAssociations: (self allowsDuplicateKeys - ifFalse: [Array with: '1' -> 'bar'] - ifTrue: [Array with: '1' -> 'foo' with: '1' -> 'bar']) - ] - - testDo [ - - | result | - result := OrderedCollection new. - collection - at: '1' put: 'foo'; - at: '2' put: 'bar'. - collection do: [:each | result add: each]. - self assert: result asArray = #('foo' 'bar') - ] - - testKeys [ - - collection - add: '1' -> 'foo'; - add: '2' -> 'bar'; - add: '1' -> 'baz'. - self assert: collection keys - = (self allowsDuplicateKeys ifTrue: [#('1' '2' '1')] ifFalse: [#('1' '2')]) - ] - - testKeysAndValuesDo [ - - | iterated | - collection keysAndValuesDo: [:key :value | self assert: false]. - collection - add: '1' -> 'foo'; - add: '2' -> 'bar'; - add: '1' -> 'baz'. - iterated := Array streamContents: - [:stream | - collection keysAndValuesDo: [:key :value | stream nextPut: key -> value]]. - self - assert: iterated size = (self allowsDuplicateKeys ifTrue: [3] ifFalse: [2]). - self assert: iterated first - = (self allowsDuplicateKeys ifTrue: ['1' -> 'foo'] ifFalse: ['1' -> 'baz']). - self assert: iterated second = ('2' -> 'bar'). - self allowsDuplicateKeys - ifTrue: [self assert: iterated third = ('1' -> 'baz')] - ] - - testKeysDo [ - - | result | - result := OrderedCollection new. - collection - add: '1' -> 'foo'; - add: '2' -> 'bar'; - add: '1' -> 'baz'. - collection keysDo: [:each | result add: each]. - self assert: result asArray - = (self allowsDuplicateKeys ifTrue: [#('1' '2' '1')] ifFalse: [#('1' '2')]) - ] - - testValues [ - - collection - add: '1' -> 'foo'; - add: '2' -> 'bar'; - add: '1' -> 'baz'. - self - assert: collection values = (self allowsDuplicateKeys - ifTrue: [#('foo' 'bar' 'baz')] - ifFalse: [#('baz' 'bar')]) - ] - - testIncludesKey [ - - self deny: (collection includesKey: '1'). - collection add: '1' -> 'foo'. - collection add: '1' -> 'bar'. - self assert: (collection includesKey: '1') - ] - - testIsCollection [ - - self assert: collection isCollection - ] - - testIsDictionary [ - - self assert: collection isDictionary - ] - - testIsEmpty [ - - self assert: collection isEmpty. - collection add: '1' -> 'foo'. - collection add: '1' -> 'bar'. - self deny: collection isEmpty - ] -] - diff --git a/grease/Tests/Core/GRStringTest.st b/grease/Tests/Core/GRStringTest.st deleted file mode 100644 index acb4ab7..0000000 --- a/grease/Tests/Core/GRStringTest.st +++ /dev/null @@ -1,269 +0,0 @@ -GRCollectionTest subclass: GRStringTest [ - - - - - allowDuplicateValues [ - - ^true - ] - - arbitraryCollection [ - - ^ 'fadbbc' copy "String literals are immutable" - ] - - collectionClass [ - - ^String - ] - - duplicateElement [ - - ^$b - ] - - excludedElement [ - - ^$Q - ] - - includedElement [ - - ^$d - ] - - isExtensible [ - - ^false - ] - - isInitializable [ - - ^true - ] - - isSequenced [ - - ^true - ] - - isSequencedReadable [ - - ^true - ] - - testAsUppercase [ - - self assert: 'abc' asUppercase = 'ABC'. - self assert: 'ABC' asUppercase = 'ABC' - ] - - testCapitalized [ - - self assert: 'capitalized' capitalized = 'Capitalized'. - self assert: 'Capitalized' capitalized = 'Capitalized'. - self assert: 'CAPITALIZED' capitalized = 'CAPITALIZED'. - self assert: #'capitalized' capitalized = #'Capitalized'. - self assert: #'Capitalized' capitalized = #'Capitalized'. - self assert: #'CAPITALIZED' capitalized = #'CAPITALIZED'. - ] - - "testCapitalizedUmlauts [ - - self assert: 'äöü' capitalized = 'Äöü'. - self assert: 'Äöü' capitalized = 'Äöü'. - self assert: 'ÄÖÜ' capitalized = 'ÄÖÜ'. - self assert: #'äöü' capitalized = #'Äöü'. - self assert: #'Äöü' capitalized = #'Äöü'. - self assert: #'ÄÖÜ' capitalized = #'ÄÖÜ' - ]" - - testCopyAfter [ - - self assert: ('de_CH' copyAfter: $_) = 'CH' - ] - - testCopyAfterLast [ - - self assert: ('britney.sex.tape.mkv' copyAfterLast: $.) = 'mkv'. - self assert: ('britney.sex.tape.mkv' copyAfterLast: $$) = '' - ] - - testCopyUpTo [ - - self assert: ('britney.sex.tape.mkv' copyUpTo: $.) = 'britney'. - self assert: ('britney.sex.tape.mkv' copyUpTo: $$) = 'britney.sex.tape.mkv' - ] - - testCopyUpToLast [ - - self assert: ('britney.sex.tape.mkv' copyUpToLast: $.) = 'britney.sex.tape' - ] - - testIncludesSubString [ - - self assert: ('britney.sex.tape.mkv' beginsWith: 'britney'). - self deny: ('britney.sex.tape.mkv' beginsWith: 'sex') - ] - - testSubStrings [ - - "#subStrings: is defined by ANSI 5.7.10.15: - Answer an array containing the substrings in the receiver separated by the elements of separators." - | mimeType tokens | - mimeType := 'application/xhtml+xml'. - tokens := mimeType subStrings: '/'. - self assert: tokens size = 2. - self assert: tokens first = 'application'. - self assert: tokens second = 'xhtml+xml'. - - "ANSI is a bit unclear on how multiple sequential delimiters should be treated. - Make sure behaviour is consistent for several delimiters in a row (taken from - Squeak's behaviour)" - tokens := 'abc,.def.ghi' subStrings: '.,'. - self assert: tokens size = 3. - self assert: tokens first = 'abc'. - self assert: tokens second = 'def'. - self assert: tokens third = 'ghi'. - ] - - testExcerpt [ - - self assert: ('abcde' excerpt: 'c' radius: 0) = '...c...'. - self assert: ('abcde' excerpt: 'c' radius: 1) = '...bcd...'. - self assert: ('abcde' excerpt: 'c' radius: 2) = 'abcde'. - self assert: ('abcde' excerpt: 'c' radius: 3) = 'abcde'. - - self assert: ('abcde' excerpt: 'c' radius: 0 ellipsis: 'x') = 'xcx'. - self assert: ('abcde' excerpt: 'c' radius: 1 ellipsis: 'x') = 'xbcdx'. - self assert: ('abcde' excerpt: 'c' radius: 2 ellipsis: 'x') = 'abcde' - ] - - testExcerptEmpty [ - - self assert: ('' excerpt: '') isNil. - self assert: ('' excerpt: 'x') isNil. - self assert: ('x' excerpt: '') isNil - ] - - testExcerptLeft [ - - self assert: ('abcde' excerpt: 'd' radius: 0 ellipsis: 'x') = 'xdx'. - self assert: ('abcde' excerpt: 'd' radius: 1 ellipsis: 'x') = 'xcde'. - self assert: ('abcde' excerpt: 'd' radius: 2 ellipsis: 'x') = 'xbcde'. - self assert: ('abcde' excerpt: 'd' radius: 3 ellipsis: 'x') = 'abcde' - ] - - testExcerptRight [ - - self assert: ('abcde' excerpt: 'b' radius: 0 ellipsis: 'x') = 'xbx'. - self assert: ('abcde' excerpt: 'b' radius: 1 ellipsis: 'x') = 'abcx'. - self assert: ('abcde' excerpt: 'b' radius: 2 ellipsis: 'x') = 'abcdx'. - self assert: ('abcde' excerpt: 'b' radius: 3 ellipsis: 'x') = 'abcde' - ] - - testInflectorAssimilated [ - - self assert: 'vertice' pluralize = 'vertices'. - self assert: 'index' pluralize = 'indices' - ] - - testInflectorCommonSuffixes [ - - self assert: 'mouse' pluralize = 'mice'. - self assert: 'synopse' pluralize = 'synopses'. - self assert: 'man' pluralize = 'men' - ] - - testInflectorFfffSuffixes [ - - self assert: 'life' pluralize = 'lives'. - self assert: 'wolf' pluralize = 'wolves' - ] - - testInflectorIrregular [ - - self assert: 'genie' pluralize = 'genies'. - self assert: 'ox' pluralize = 'oxen'. - self assert: 'cow' pluralize = 'kine'. - self assert: 'child' pluralize = 'children'. - self assert: 'woman' pluralize = 'women' - ] - - testInflectorNotInflecting [ - - self assert: 'fish' pluralize = 'fish'. - self assert: 'travois' pluralize = 'travois'. - self assert: 'chassis' pluralize = 'chassis'. - self assert: 'nationalities' pluralize = 'nationalities' - ] - - testInflectorTsssSuffixes [ - - self assert: 'church' pluralize = 'churches'. - self assert: 'class' pluralize = 'classes' - ] - - testInflectorYyyySuffixes [ - - self assert: 'story' pluralize = 'stories'. - self assert: 'lady' pluralize = 'ladies'. - self assert: 'stay' pluralize = 'stays'. - ] - - testTrimBoth [ - - self assert: '' trimBoth = ''. - self assert: ' ' trimBoth = ''. - self assert: ' ' trimBoth = ''. - self assert: 'foo' trimBoth = 'foo'. - self assert: ' foo ' trimBoth = 'foo'. - self assert: ' foo ' trimBoth = 'foo'. - self assert: ((String with: Character cr), ' foo ') trimBoth = 'foo'. - - self assert: ('aabbaa' trimBoth: [ :each | each = $a ]) = 'bb'. - self assert: ('bbaabb' trimBoth: [ :each | each = $a ]) = 'bbaabb' - ] - - testTrimLeft [ - - self assert: '' trimLeft = ''. - self assert: ' ' trimLeft = ''. - self assert: ' ' trimLeft = ''. - self assert: 'foo' trimLeft = 'foo'. - self assert: ' foo ' trimLeft = 'foo '. - self assert: ' foo ' trimLeft = 'foo '. - - self assert: ('aabbaa' trimLeft: [ :each | each = $a ]) = 'bbaa'. - self assert: ('bbaabb' trimLeft: [ :each | each = $a ]) = 'bbaabb' - ] - - testTrimRight [ - - self assert: '' trimRight = ''. - self assert: ' ' trimRight = ''. - self assert: ' ' trimRight = ''. - self assert: 'foo' trimRight = 'foo'. - self assert: ' foo ' trimRight = ' foo'. - self assert: ' foo ' trimRight = ' foo'. - - self assert: ('aabbaa' trimRight: [ :each | each = $a ]) = 'aabb'. - self assert: ('bbaabb' trimRight: [ :each | each = $a ]) = 'bbaabb' - ] - - testTruncate [ - - self assert: ('abc' truncate) = 'abc'. - self assert: ('abc' truncate: 3) = 'abc'. - self assert: ('abc' truncate: 2) = 'ab...'. - - self assert: ('abc' truncate: 1 ellipsis: '') = 'a'. - self assert: ('abc' truncate: 0 ellipsis: 'none') = 'none' - ] - - testTruncateEmpty [ - - self assert: '' truncate = '' - ] -] diff --git a/grease/Tests/Core/GRUtf8CodecTest.st b/grease/Tests/Core/GRUtf8CodecTest.st deleted file mode 100644 index 115cc5b..0000000 --- a/grease/Tests/Core/GRUtf8CodecTest.st +++ /dev/null @@ -1,76 +0,0 @@ -TestCase subclass: GRUtf8CodecTest [ - - - - - asString: aCollectionOfIntegers [ - - ^aCollectionOfIntegers asByteArray asString - ] - - seasideByteArray [ - - ^#(83 101 97 115 105 100 101) asByteArray "Seaside" - ] - - decodedString [ - - ^'Ãœbèrstrîñgé' - ] - - utf8String [ - - ^self asString: - #(195 156 98 195 168 114 115 116 114 195 174 195 177 103 195 169) - ] - - testCodecUtf8 [ - - #('UTF-8' 'utf-8') do: - [:codecName | - | codec | - codec := GRCodec forEncoding: codecName. - self assert: codec name = codecName. - self assert: codec url name = codecName. - self assert: (codec encode: self decodedString) = self utf8String. - self assert: (codec url encode: self decodedString) = self utf8String. - self assert: (codec decode: self utf8String) = self decodedString. - self assert: (codec url decode: self utf8String) = self decodedString] - ] - - testCodecUtf8Bom [ - - #('UTF-8' 'utf-8') do: - [:codecName | - | codec bom | - codec := GRCodec forEncoding: codecName. - bom := self asString: #(239 187 191). - self assert: (codec decode: bom , self utf8String) = self decodedString. - self assert: (codec url decode: bom , self utf8String) = self decodedString] - ] - - testCodecUtf8ShortestForm [ - "Non shortest form characters should be rejected - See Corrigendum #1: UTF-8 Shortest Form http://www.unicode.org/versions/corrigendum1.html" - - - #('UTF-8' 'utf-8') do: - [:codecName | - | codec abc | - codec := GRCodec forEncoding: codecName. - abc := self asString: #(193 129 193 130 193 131). - [self - should: [self assert: (codec decode: abc) ~= 'ABC'] - raise: Error]] - ] - - testNext [ - - | stream | - stream := (GRCodec forEncoding: 'utf8') - encoderFor: self seasideByteArray readStream. - self assert: stream next = $S. - self assert: (stream next: 1) = 'e' - ] -] - diff --git a/grease/Tests/Core/GRVersionTest.st b/grease/Tests/Core/GRVersionTest.st deleted file mode 100644 index a702451..0000000 --- a/grease/Tests/Core/GRVersionTest.st +++ /dev/null @@ -1,183 +0,0 @@ -TestCase subclass: GRVersionTest [ - - - - - assert: aVersionArray equals: bVersionArray [ - - | a b | - a := self buildVersion: aVersionArray. - b := self buildVersion: bVersionArray. - self deny: a < b. - self assert: a <= b. - self deny: b < a. - self assert: b <= a. - self deny: b > a. - self assert: b >= a. - self deny: a > b. - self assert: a >= b. - self assert: a = b - ] - - assert: aVersionArray sortsBefore: bVersionArray [ - - | a b | - a := self buildVersion: aVersionArray. - b := self buildVersion: bVersionArray. - self assert: a < b. - self assert: a <= b. - self deny: b < a. - self deny: b <= a. - self assert: b > a. - self assert: b >= a. - self deny: a > b. - self deny: a >= b. - self deny: a = b - ] - - buildVersion: anArray [ - - ^(GRVersion - major: (anArray at: 1 ifAbsent: [nil]) - minor: (anArray at: 2 ifAbsent: [nil]) - revision: (anArray at: 3 ifAbsent: [nil])) - stage: (anArray at: 4 ifAbsent: [nil]) - number: (anArray at: 5 ifAbsent: [nil]); - yourself - ] - - testComparison [ - - self assert: #(1) sortsBefore: #(2). - self assert: #(2) sortsBefore: #(10). - self assert: #(1) sortsBefore: #(1 1). - self assert: #(1 nil nil #alpha) sortsBefore: #(1). - self assert: #(1 nil nil #alpha) sortsBefore: #(1 0). - self assert: #(1 nil nil #alpha) sortsBefore: #(1 0 0). - self assert: #(1 0) sortsBefore: #(2). - self assert: #(1 0) sortsBefore: #(2 0). - self assert: #(1 0) sortsBefore: #(1 1). - self assert: #(1 2) sortsBefore: #(1 10). - self assert: #(1 0 nil #alpha) sortsBefore: #(1 0). - self assert: #(1 0 nil #alpha) sortsBefore: #(1 0 0). - self assert: #(1 0 0) sortsBefore: #(2). - self assert: #(1 0 0) sortsBefore: #(1 1). - self assert: #(1 0 1) sortsBefore: #(1 1). - self assert: #(1 0 1 #alpha) sortsBefore: #(1 1). - self assert: #(1 1 0 #alpha) sortsBefore: #(1 1). - self assert: #(1 1 0 #alpha 2) sortsBefore: #(1 1). - self assert: #(1 1 0 #beta) sortsBefore: #(1 1). - self assert: #(1 1 0 #beta 2) sortsBefore: #(1 1). - self assert: #(1 nil nil #alpha) sortsBefore: #(1 nil nil #alpha 2). - self assert: #(1 nil nil #beta) sortsBefore: #(1 nil nil #beta 2). - self assert: #(1 0 nil #alpha) sortsBefore: #(1 0 nil #alpha 2). - self assert: #(1 0 nil #beta) sortsBefore: #(1 0 nil #beta 2). - self assert: #(1 0 0 #alpha) sortsBefore: #(1 0 0 #alpha 2). - self assert: #(1 0 0 #beta) sortsBefore: #(1 0 0 #beta 2) - ] - - testConvenience [ - - | version | - version := GRVersion - major: 1 - minor: 2 - revision: 3. - self assert: version stage isNil. - self assert: version stageNumber isNil. - self assert: version isFinal. - self deny: version isAlpha. - self deny: version isBeta. - version beAlpha. - self assert: version stage = #alpha. - self assert: version stageNumber isNil. - self assert: version isAlpha. - self deny: version isBeta. - self deny: version isFinal. - version beBeta. - self assert: version stage = #beta. - self assert: version stageNumber isNil. - self assert: version isBeta. - self deny: version isAlpha. - self deny: version isFinal. - version beAlpha: 1. - self assert: version stage = #alpha. - self assert: version stageNumber = 1. - self assert: version isAlpha. - self deny: version isBeta. - self deny: version isFinal. - version beBeta: 1. - self assert: version stage = #beta. - self assert: version stageNumber = 1. - self assert: version isBeta. - self deny: version isAlpha. - self deny: version isFinal. - version beFinal. - self assert: version stage isNil. - self assert: version stageNumber isNil. - self assert: version isFinal. - self deny: version isAlpha. - self deny: version isBeta - ] - - testEquality [ - - self assert: #(1) equals: #(1). - self assert: #(1) equals: #(1 0). - self assert: #(1) equals: #(1 0 0). - self assert: #(1 0) equals: #(1 0). - self assert: #(1 0) equals: #(1 0 0). - self assert: #(1 0 0) equals: #(1 0 0). - self assert: #(1 0 0 #alpha) equals: #(1 0 0 #alpha 1). - self assert: #(1 0 0 #beta) equals: #(1 0 0 #beta 1) - ] - - testStringConversion [ - - self - assert: (GRVersion - major: 1 - minor: 2 - revision: 3) greaseString - = '1.2.3'. - self - assert: (GRVersion - major: 11 - minor: 12 - revision: 13) greaseString - = '11.12.13'. - self assert: (GRVersion major: 1 minor: 2) greaseString = '1.2'. - self - assert: (GRVersion - major: 1 - minor: 2 - revision: 0) greaseString - = '1.2.0'. - self assert: (GRVersion major: 1) greaseString = '1.0'. - self - assert: (GRVersion - major: 1 - minor: 2 - revision: 3) beAlpha - greaseString = '1.2.3alpha'. - self - assert: ((GRVersion - major: 1 - minor: 2 - revision: 3) beAlpha: 1) - greaseString = '1.2.3alpha1'. - self - assert: (GRVersion - major: 1 - minor: 2 - revision: 3) beBeta - greaseString = '1.2.3beta'. - self - assert: ((GRVersion - major: 1 - minor: 2 - revision: 3) beBeta: 1) - greaseString = '1.2.3beta1' - ] -] - diff --git a/grease/Tests/GST/Core/GRGSTPlatformTest.st b/grease/Tests/GST/Core/GRGSTPlatformTest.st deleted file mode 100644 index d91073c..0000000 --- a/grease/Tests/GST/Core/GRGSTPlatformTest.st +++ /dev/null @@ -1,89 +0,0 @@ -TestCase subclass: GRGSTPlatformTest [ - - - - - testCompileIntoClassified [ - - | source protocol selectors selector | - source := 'aMethod - [^ ''a result'']'. - protocol := 'a-protocol'. - selector := #aMethod. - GRPlatform current - compile: source - into: self class - classified: protocol. - [self assert: (self class selectors includes: selector). - self assert: (self class whichCategoryIncludesSelector: selector) = protocol] - ensure: [self class removeSelector: selector] - ] - - testConvertToSmalltalkNewlines [ - - | expected euro | - expected := 'selector' , (String with: Character cr) , '"comment"'. - self assert: expected - = (GRPlatform current convertToSmalltalkNewlines: expected). - self assert: expected = (GRPlatform current - convertToSmalltalkNewlines: 'selector' , (String with: Character lf) - , '"comment"'). - self assert: expected = (GRPlatform current - convertToSmalltalkNewlines: 'selector' - , (String with: Character cr with: Character lf) , '"comment"'). - euro := UnicodeString with: (UnicodeCharacter codePoint: 8364). - self assert: (expected asUnicodeString, euro) - = (GRPlatform current convertToSmalltalkNewlines: expected asUnicodeString, euro). - self assert: (GRPlatform current convertToSmalltalkNewlines: nil) isNil - ] - - testFullName [ - - self assert: Object fullName = 'Object' - ] - - testGreaseIntegerOnCharacter [ - - | character | - character := Character codePoint: 19982. - self assert: character greaseInteger = 19982. - character := UnicodeCharacter value: 19982. - self assert: character greaseInteger = 19982. - ] - - testDirectedMessageValueWithPossibleArguments [ - - | send | - send := DirectedMessage receiver: 1 selector: #+. - self assert: (send valueWithPossibleArguments: (Array with: 2)) = 3. - self assert: (send valueWithArguments: (Array with: 2)) = 3. - self assert: (send value: 2) = 3. - send := DirectedMessage receiver: false selector: #not. - self assert: (send valueWithPossibleArguments: (Array with: 3)). - send := DirectedMessage - receiver: 1 - selector: #+ - arguments: #(2). - self assert: (send valueWithPossibleArguments: (Array with: 4)) = 3. - self assert: send value = 3. - send := DirectedMessage - receiver: Array - selector: #with:with: - arguments: #(1). - self assert: (send valueWithPossibleArguments: (Array with: 2)) size = 2. - send := DirectedMessage receiver: Array selector: #with:with:. - self assert: (send value: 1 value: 2) size = 2. - send := DirectedMessage receiver: 1 selector: #+. - self assert: send argumentCount = 1. - self assert: send arguments size = 0. - self assert: send fixCallbackTemps == send. - send := DirectedMessage - receiver: 1 - selector: #+ - argument: 2. - self assert: send argumentCount isZero. - self assert: send arguments size = 1. - self assert: send fixCallbackTemps == send - ] -] - diff --git a/grease/package.st b/grease/package.st deleted file mode 100644 index 77d1189..0000000 --- a/grease/package.st +++ /dev/null @@ -1,81 +0,0 @@ -Eval [ - PackageBuilder new - name: 'Grease'; - namespace: 'Grease'; - prereq: 'Iconv'; - prereq: 'Digest'; - prereq: 'SUnit'; - - testsBelow: 'Tests' matching: '*.st'; - - url: 'git://github.com/NicolasPetton/Grease.git'; - - filein: 'Core/GRObject.st'; - filein: 'Core/GRPlatform.st'; - filein: 'Core/GRPackage.st'; - filein: 'Core/GRVersion.st'; - filein: 'Core/Exceptions.st'; - filein: 'Core/Extensions.st'; - - filein: 'Core/Collections/GRSmallDictionary.st'; - filein: 'Core/Collections/GROrderedMultiMap.st'; - - filein: 'Core/Text/GRCodec.st'; - filein: 'Core/Text/GRNullCodec.st'; - filein: 'Core/Text/GRCodecStream.st'; - filein: 'Core/Text/GRNullCodecStream.st'; - filein: 'Core/Text/GRInflector.st'; - filein: 'Core/Text/GRInvalidUtf8Error.st'; - filein: 'Core/Text/GRPrinter.st'; - filein: 'Core/Text/GRMappedPrinter.st'; - filein: 'Core/Text/GRNumberPrinter.st'; - filein: 'Core/Text/GROrdinalizePrinter.st'; - filein: 'Core/Text/GRPluggablePrinter.st'; - filein: 'Core/Text/GRSequentialPrinter.st'; - filein: 'Core/Text/GRSignPrinter.st'; - filein: 'Core/Text/GRStringPrinter.st'; - filein: 'Core/Text/GRUnitPrinter.st'; - filein: 'Core/Text/GRUnsupportedEncodingError.st'; - - filein: 'Core/Utilities/GRDelayedSend.st'; - filein: 'Core/Utilities/GRBoundDelayedSend.st'; - filein: 'Core/Utilities/GRUnboundDelayedSend.st'; - filein: 'Core/Utilities/GRInvalidArgumentCount.st'; - - filein: 'GST/Core/Extensions.st'; - filein: 'GST/Core/GRGSTGenericCodec.st'; - filein: 'GST/Core/GRGSTPlatform.st'; - filein: 'GST/Core/GRGSTRandomProvider.st'; - - filein: 'Tests/Core/GRCodecTest.st'; - filein: 'Tests/Core/GRCollectionTest.st'; - filein: 'Tests/Core/GRAbstractDictionaryTest.st'; - filein: 'Tests/Core/GRDictionaryTest.st'; - filein: 'Tests/Core/GRIdentityDictionaryTest.st'; - filein: 'Tests/Core/GRArrayTest.st'; - filein: 'Tests/Core/GRBagTest.st'; - filein: 'Tests/Core/GRIntervalTest.st'; - filein: 'Tests/Core/GROrderedCollectionTest.st'; - filein: 'Tests/Core/GRSetTest.st'; - filein: 'Tests/Core/GRStringTest.st'; - filein: 'Tests/Core/GRDelayedSendTest.st'; - filein: 'Tests/Core/GRDurationTest.st'; - filein: 'Tests/Core/GRErrorStub.st'; - filein: 'Tests/Core/GRExceptionTest.st'; - filein: 'Tests/Core/GRNotificationStub.st'; - filein: 'Tests/Core/GRNullCodecStreamTest.st'; - filein: 'Tests/Core/GRNumberTest.st'; - filein: 'Tests/Core/GRObjectStub.st'; - filein: 'Tests/Core/GRObjectTest.st'; - filein: 'Tests/Core/GRPackageTest.st'; - filein: 'Tests/Core/GRPlatformTest.st'; - filein: 'Tests/Core/GRPrinterTest.st'; - filein: 'Tests/Core/GRSmallDictionaryTest.st'; - filein: 'Tests/Core/GROrderedMultiMapTest.st'; - filein: 'Tests/Core/GRUtf8CodecTest.st'; - filein: 'Tests/Core/GRVersionTest.st'; - - filein: 'Tests/GST/Core/GRGSTPlatformTest.st'; - - buildXml -] diff --git a/grease/package.xml b/grease/package.xml deleted file mode 100644 index ee3e7a1..0000000 --- a/grease/package.xml +++ /dev/null @@ -1,213 +0,0 @@ - - Grease - git://github.com/NicolasPetton/Grease.git - Grease - Iconv - Digest - SUnit - - Tests/Core/GRCodecTest.st - Tests/Core/GRIntervalTest.st - Tests/Core/GRNumberTest.st - Tests/Core/GRDelayedSendTest.st - Tests/Core/GRExceptionTest.st - Tests/Core/GRDictionaryTest.st - Tests/Core/GRErrorStub.st - Tests/Core/GRObjectStub.st - Tests/Core/GRBagTest.st - Tests/Core/GRNullCodecStreamTest.st - Tests/Core/GRVersionTest.st - Tests/Core/GRDurationTest.st - Tests/Core/GRSmallDictionaryTest.st - Tests/Core/GRUtf8CodecTest.st - Tests/Core/GRSetTest.st - Tests/Core/GRPlatformTest.st - Tests/Core/GRPrinterTest.st - Tests/Core/GRObjectTest.st - Tests/Core/GRNotificationStub.st - Tests/Core/GRPackageTest.st - Tests/Core/GRCollectionTest.st - Tests/Core/GRArrayTest.st - Tests/Core/GROrderedMultiMapTest.st - Tests/Core/GROrderedCollectionTest.st - Tests/Core/GRIdentityDictionaryTest.st - Tests/Core/GRStringTest.st - Tests/Core/GRAbstractDictionaryTest.st - Tests/GST/Core/GRGSTPlatformTest.st - Tests/Core/GRCodecTest.st - Tests/Core/GRIntervalTest.st - Tests/Core/GRNumberTest.st - Tests/Core/GRDelayedSendTest.st - Tests/Core/GRExceptionTest.st - Tests/Core/GRDictionaryTest.st - Tests/Core/GRErrorStub.st - Tests/Core/GRObjectStub.st - Tests/Core/GRBagTest.st - Tests/Core/GRNullCodecStreamTest.st - Tests/Core/GRVersionTest.st - Tests/Core/GRDurationTest.st - Tests/Core/GRSmallDictionaryTest.st - Tests/Core/GRUtf8CodecTest.st - Tests/Core/GRSetTest.st - Tests/Core/GRPlatformTest.st - Tests/Core/GRPrinterTest.st - Tests/Core/GRObjectTest.st - Tests/Core/GRNotificationStub.st - Tests/Core/GRPackageTest.st - Tests/Core/GRCollectionTest.st - Tests/Core/GRArrayTest.st - Tests/Core/GROrderedMultiMapTest.st - Tests/Core/GROrderedCollectionTest.st - Tests/Core/GRIdentityDictionaryTest.st - Tests/Core/GRStringTest.st - Tests/Core/GRAbstractDictionaryTest.st - Tests/GST/Core/GRGSTPlatformTest.st - - Grease.GRCodecTest - Grease.GRIntervalTest - Grease.GRNumberTest - Grease.GRDelayedSendTest - Grease.GRExceptionTest - Grease.GRDictionaryTest - Grease.GRBagTest - Grease.GRNullCodecStreamTest - Grease.GRVersionTest - Grease.GRDurationTest - Grease.GRSmallDictionaryTest - Grease.GRUtf8CodecTest - Grease.GRSetTest - Grease.GRPlatformTest - Grease.GRPrinterTest - Grease.GRObjectTest - Grease.GRPackageTest - Grease.GRCollectionTest - Grease.GRArrayTest - Grease.GROrderedMultiMapTest - Grease.GROrderedCollectionTest - Grease.GRIdentityDictionaryTest - Grease.GRStringTest - Grease.GRAbstractDictionaryTest - Grease.GRGSTPlatformTest - - - Core/GRObject.st - Core/GRPlatform.st - Core/GRPackage.st - Core/GRVersion.st - Core/Exceptions.st - Core/Extensions.st - Core/Collections/GRSmallDictionary.st - Core/Collections/GROrderedMultiMap.st - Core/Text/GRCodec.st - Core/Text/GRNullCodec.st - Core/Text/GRCodecStream.st - Core/Text/GRNullCodecStream.st - Core/Text/GRInflector.st - Core/Text/GRInvalidUtf8Error.st - Core/Text/GRPrinter.st - Core/Text/GRMappedPrinter.st - Core/Text/GRNumberPrinter.st - Core/Text/GROrdinalizePrinter.st - Core/Text/GRPluggablePrinter.st - Core/Text/GRSequentialPrinter.st - Core/Text/GRSignPrinter.st - Core/Text/GRStringPrinter.st - Core/Text/GRUnitPrinter.st - Core/Text/GRUnsupportedEncodingError.st - Core/Utilities/GRDelayedSend.st - Core/Utilities/GRBoundDelayedSend.st - Core/Utilities/GRUnboundDelayedSend.st - Core/Utilities/GRInvalidArgumentCount.st - GST/Core/Extensions.st - GST/Core/GRGSTGenericCodec.st - GST/Core/GRGSTPlatform.st - GST/Core/GRGSTRandomProvider.st - Tests/Core/GRCodecTest.st - Tests/Core/GRCollectionTest.st - Tests/Core/GRAbstractDictionaryTest.st - Tests/Core/GRDictionaryTest.st - Tests/Core/GRIdentityDictionaryTest.st - Tests/Core/GRArrayTest.st - Tests/Core/GRBagTest.st - Tests/Core/GRIntervalTest.st - Tests/Core/GROrderedCollectionTest.st - Tests/Core/GRSetTest.st - Tests/Core/GRStringTest.st - Tests/Core/GRDelayedSendTest.st - Tests/Core/GRDurationTest.st - Tests/Core/GRErrorStub.st - Tests/Core/GRExceptionTest.st - Tests/Core/GRNotificationStub.st - Tests/Core/GRNullCodecStreamTest.st - Tests/Core/GRNumberTest.st - Tests/Core/GRObjectStub.st - Tests/Core/GRObjectTest.st - Tests/Core/GRPackageTest.st - Tests/Core/GRPlatformTest.st - Tests/Core/GRPrinterTest.st - Tests/Core/GRSmallDictionaryTest.st - Tests/Core/GROrderedMultiMapTest.st - Tests/Core/GRUtf8CodecTest.st - Tests/Core/GRVersionTest.st - Tests/GST/Core/GRGSTPlatformTest.st - Core/GRObject.st - Core/GRPlatform.st - Core/GRPackage.st - Core/GRVersion.st - Core/Exceptions.st - Core/Extensions.st - Core/Collections/GRSmallDictionary.st - Core/Collections/GROrderedMultiMap.st - Core/Text/GRCodec.st - Core/Text/GRNullCodec.st - Core/Text/GRCodecStream.st - Core/Text/GRNullCodecStream.st - Core/Text/GRInflector.st - Core/Text/GRInvalidUtf8Error.st - Core/Text/GRPrinter.st - Core/Text/GRMappedPrinter.st - Core/Text/GRNumberPrinter.st - Core/Text/GROrdinalizePrinter.st - Core/Text/GRPluggablePrinter.st - Core/Text/GRSequentialPrinter.st - Core/Text/GRSignPrinter.st - Core/Text/GRStringPrinter.st - Core/Text/GRUnitPrinter.st - Core/Text/GRUnsupportedEncodingError.st - Core/Utilities/GRDelayedSend.st - Core/Utilities/GRBoundDelayedSend.st - Core/Utilities/GRUnboundDelayedSend.st - Core/Utilities/GRInvalidArgumentCount.st - GST/Core/Extensions.st - GST/Core/GRGSTGenericCodec.st - GST/Core/GRGSTPlatform.st - GST/Core/GRGSTRandomProvider.st - Tests/Core/GRCodecTest.st - Tests/Core/GRCollectionTest.st - Tests/Core/GRAbstractDictionaryTest.st - Tests/Core/GRDictionaryTest.st - Tests/Core/GRIdentityDictionaryTest.st - Tests/Core/GRArrayTest.st - Tests/Core/GRBagTest.st - Tests/Core/GRIntervalTest.st - Tests/Core/GROrderedCollectionTest.st - Tests/Core/GRSetTest.st - Tests/Core/GRStringTest.st - Tests/Core/GRDelayedSendTest.st - Tests/Core/GRDurationTest.st - Tests/Core/GRErrorStub.st - Tests/Core/GRExceptionTest.st - Tests/Core/GRNotificationStub.st - Tests/Core/GRNullCodecStreamTest.st - Tests/Core/GRNumberTest.st - Tests/Core/GRObjectStub.st - Tests/Core/GRObjectTest.st - Tests/Core/GRPackageTest.st - Tests/Core/GRPlatformTest.st - Tests/Core/GRPrinterTest.st - Tests/Core/GRSmallDictionaryTest.st - Tests/Core/GROrderedMultiMapTest.st - Tests/Core/GRUtf8CodecTest.st - Tests/Core/GRVersionTest.st - Tests/GST/Core/GRGSTPlatformTest.st - diff --git a/iliad-stable/.gitignore b/iliad-stable/.gitignore deleted file mode 100644 index 2a8427d..0000000 --- a/iliad-stable/.gitignore +++ /dev/null @@ -1,10 +0,0 @@ -Public/images/arrow_down.png -Public/images/arrow_right.png -Public/stylesheets/iliad-ui.css -gst.log -iliad.im -iliad.log -log.log -iliad.pidaproject -make_packages.log - diff --git a/iliad-stable/ACKNOWLEDGEMENTS b/iliad-stable/ACKNOWLEDGEMENTS deleted file mode 100644 index 07020df..0000000 --- a/iliad-stable/ACKNOWLEDGEMENTS +++ /dev/null @@ -1,44 +0,0 @@ -Acknowledgements ----------------- - -The following parts of Iliad reuses portions of code from the Seaside framework: -- The Widget class and its decorators -- The HTTP abstraction library -- The Swazoo adapter - -Seaside is licenced under the MIT Licence. -Copyright © 2001–2009 Avi Bryant, Julian Fitzell -Copyright © 2007–2009 Lukas Renggli, Michel Bany, Philippe Marschall -Copyright © Seaside Contributors - -http://www.seaside.st/about/licence - ----------------- - -The JSON library is adapted from http://www.squeaksource.com/Diplomacy/ -written by Avi Bryant and licenced under the MIT licence. - ----------------- - -The Application class reuses code from HttpView2. -HttpView2 is written by Göran Krampe and Giovanni Corriga and licenced -under the MIT licence. - -http://www.squeaksource.com/HttpView2 - ----------------- - -The Element hierarchy is widely inspired from the Aida/Web web framework, -written by Janko Mivsek. -Aida/Web is licenced under the MIT licence - -Copyright (c) 2000-2007 Janko MivÅ¡ek -Copyright (c) 2007-2009 Janko MivÅ¡ek, Nicolas Petton, contributors - -http://www.aidaweb.si - ----------------- - -The javascript layer is inspired by the LISP web framework Weblocks -http://weblocks.viridian-project.de/ - diff --git a/iliad-stable/Core/Buildables/Extensions.st b/iliad-stable/Core/Buildables/Extensions.st deleted file mode 100644 index 97a576e..0000000 --- a/iliad-stable/Core/Buildables/Extensions.st +++ /dev/null @@ -1,60 +0,0 @@ -"====================================================================== -| -| Smalltalk Classes extensions -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -Object extend [ - - asResponse [ - - | response | - response := Iliad.ILResponse ok. - self respondOn: response. - ^response - ] - - respondOn: aResponse [ - - self displayOn: aResponse - ] -] - -BlockClosure extend [ - - buildOn: anElement [ - - self value: anElement - ] -] diff --git a/iliad-stable/Core/Buildables/ILAnswerHandler.st b/iliad-stable/Core/Buildables/ILAnswerHandler.st deleted file mode 100644 index 4f4b2ac..0000000 --- a/iliad-stable/Core/Buildables/ILAnswerHandler.st +++ /dev/null @@ -1,66 +0,0 @@ -"====================================================================== -| -| Iliad.ILAnswerHandler class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Some parts of this file reuse code from the Seaside framework written -| by Avi Bryant, Julian Fitzell, Lukas Renggli, Michel Bany, Philippe -| Marschall and Seaside contributors http://www.seaside.st -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILDecorator subclass: ILAnswerHandler [ - | action | - - - >show:onAnswer:'> - - action [ - - ^action - ] - - action: anAction [ - - action := anAction - ] - - handleAnswer: anAnswer [ - - (self action) - value: anAnswer; - evaluate - ] -] - diff --git a/iliad-stable/Core/Buildables/ILAppendDelegator.st b/iliad-stable/Core/Buildables/ILAppendDelegator.st deleted file mode 100644 index 729ec70..0000000 --- a/iliad-stable/Core/Buildables/ILAppendDelegator.st +++ /dev/null @@ -1,53 +0,0 @@ -"====================================================================== -| -| Iliad.ILAppendDelegator class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2009 -| Nicolas Petton , -| Sébastien Audier -| -| Some parts of this file reuse code from the Seaside framework written -| by Avi Bryant, Julian Fitzell, Lukas Renggli, Michel Bany, Philippe -| Marschall and Seaside contributors http://www.seaside.st -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILDelegator subclass: ILAppendDelegator [ - - - - - contents [ - - ^[:e | e - build: self decoratee contents; - build: super contents] - ] -] diff --git a/iliad-stable/Core/Buildables/ILApplication.st b/iliad-stable/Core/Buildables/ILApplication.st deleted file mode 100644 index dfb4ce5..0000000 --- a/iliad-stable/Core/Buildables/ILApplication.st +++ /dev/null @@ -1,298 +0,0 @@ -"====================================================================== -| -| Iliad.ILApplication class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Some parts of this file reuse code from HttpView2 written by Giovanni -| Corriga and Göran Krampe http://www.squeaksource.com/HttpView2/ -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILBuildable subclass: ILApplication [ - | model page | - - - is used to filter controller methods. -By default it allows all methods in the ''controllers'' protocol. - -Alternatively, you can override the class method #defaultSelectorFilter to supply -your own selectorFilter or plug it in using the class method #selectorFilter:'> - - ILApplication class [ - | selectorFilter | - - path [ - "Base path of the application. - Override this method in concrete subclasses. - It should return a string" - - - ^'' - ] - - absolutePath [ - - ^String streamContents: [:stream | - (self path startsWith: '/') ifFalse: [stream nextPut: $/]. - stream nextPutAll: self path] - ] - - selectorFilter [ - - ^selectorFilter ifNil: [self defaultSelectorFilter] - ] - - selectorFilter: aBlock [ - - selectorFilter := aBlock - ] - - defaultSelectorFilter [ - "Override this method to supply your own selectorFilter - or plug it in using #selectorFilter:" - - - ^[:selector | - (self canUnderstand: selector) and: [ - (self - categoryOfElement: selector - inClassOrSuperclass: self) = 'controllers']] - ] - - categoryOfElement: aSelector inClassOrSuperclass: aClass [ - "Find the first category of up the superclass chain." - - - ^aClass ifNotNil: [ - ^(aClass whichCategoryIncludesSelector: aSelector) ifNil: [ - self - categoryOfElement: aSelector - inClassOrSuperclass: aClass superclass]] - ] - ] - - model [ - - ^model - ] - - model: anObject [ - - model := anObject - ] - - page [ - - ^page - ] - - selectorFilter [ - - ^self class selectorFilter - ] - - widgetFor: aBuildable [ - "Convenience method. This is useful for building anonymous widgets. - ex: myWidget := self widgetFor: [:e | e h1: 'Hello world!']" - - - ^ILPluggableWidget new - contentsBlock: aBuildable; - yourself - ] - - buildContents [ - "Call #dispatch. A buildable is expected from #dispatch" - - - ^self newRootElement - build: self dispatch; - yourself - ] - - allowedSelector: aSelector [ - "Answer true if is ok to call from a URL. - Default implementation is to use the pluggable filter block." - - - ^self selectorFilter copy value: aSelector - ] - - dispatch [ - "Dispatch to correct controller method. - If dispatchOverride returns something - different from nil, consider it handled." - - - ^self dispatchOverride ifNil: [ - self dispatchOn: self router controller] - ] - - dispatchOn: aMethod [ - "Dispatch to correct method: - - If is empty we call #index - - If the selector is allowed to be executed then we just call it" - - - | m | - (aMethod isNil or: [aMethod isEmpty]) - ifTrue: [m := #index] - ifFalse: [m := aMethod asSymbol]. - (self allowedSelector: m) - ifTrue: [^self perform: m] - ifFalse: [ILDispatchError signal] - ] - - dispatchOverride [ - "Handle special urls. Subclass implementors - should call super first and see if it was handled." - - - ^nil - ] - - updatePage: aPage [ - "Override to add elements to aPage. - super should always be called" - - - aPage head javascript src: '/javascripts/jquery-1.8.3.min.js'. - aPage head javascript src: '/javascripts/no_conflict.js'. - aPage head javascript src: '/javascripts/iliad.js'. - ] - - updateFromRoute: aRoute [ - - "Override this method to update to state of the application - from the request url route. - - This method will be called for each new request" - - ] - - updateBaseUrl: anUrl [ - - "Update the base url used for the current context" - - ] - - respond: aBlock [ - "Abort all other request handling" - - - | response | - response := ILResponse new. - aBlock value: response. - self returnResponse: response - ] - - returnResponse: aResponse [ - "Abort all other request handling" - - - ILResponseNotification new - response: aResponse; - signal - ] - - index [ - "default view method" - - - ^[:e | ] - ] - - respondOn: aResponse [ - - page := self defaultPageClass new. - page body build: self. - self updatePage: page. - self context builtWidgets do: [:each | each buildHead: page head]. - page respondOn: aResponse - ] - - defaultPageClass [ - - ^ILHTMLPage - ] - - rootElementClass [ - - ^ILHTMLBuilderElement - ] - - newRootElement [ - - ^self rootElementClass new - ] -] diff --git a/iliad-stable/Core/Buildables/ILBuildable.st b/iliad-stable/Core/Buildables/ILBuildable.st deleted file mode 100644 index 629c17a..0000000 --- a/iliad-stable/Core/Buildables/ILBuildable.st +++ /dev/null @@ -1,195 +0,0 @@ -"====================================================================== -| -| Iliad.ILBuildable class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Some parts of this file reuse code from the Seaside framework written -| by Avi Bryant, Julian Fitzell, Lukas Renggli, Michel Bany, Philippe -| Marschall and Seaside contributors http://www.seaside.st -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILObject subclass: ILBuildable [ - | attributes children | - - - - - children [ - - ^children ifNil: [children := OrderedCollection new] - ] - - router [ - - ^self context router - ] - - attributeAt: aSymbol [ - - ^self attributes at: aSymbol ifAbsent: [nil] - ] - - attributeAt: aSymbol ifAbsentPut: aBlock [ - - ^self attributes at: aSymbol ifAbsentPut: aBlock - ] - - attributeAt: aSymbol put: anObject [ - - ^self attributes at: aSymbol put: anObject - ] - - attributes [ - - ^attributes ifNil: [attributes := Dictionary new] - ] - - send: aSymbol [ - - ^self send: aSymbol to: self - ] - - send: aSymbol to: anObject [ - - ^self send: aSymbol to: anObject arguments: #() - ] - - send: aSymbol to: anObject arguments: anArray [ - - ^Grease.GRDelayedSend - receiver: anObject - selector: aSymbol - arguments: anArray - ] - - build [ - - self withChildrenRegistrationDo: [ - ^self buildContents - ] - ] - - buildContents [ - "Override this method in subclasses. - It must answer an Element" - - - self subclassResponsibility - ] - - buildOn: anElement [ - - anElement add: self build - ] - - registerChild: aBuildable [ - - (self children includes: aBuildable) ifFalse: [ - self children add: aBuildable] - ] - - redirectTo: anUrlString [ - "Abort all other request handling. - Redirect to anUrlString" - - - self session - redirectUrl: anUrlString; - redirect - ] - - redirectToIndex [ - "Abort all other request handling. - Redirect to the index method of this class" - - - self redirectToLocal: 'index' - ] - - redirectToLocal: aString [ - "Abort all other request handling. - Make a redirection to another controller method in this application" - - - self - redirectToApplication: self application class - controller: aString - ] - - redirectToApplication: aClass [ - "Abort all other request handling. - Redirect to the index method of " - - - self redirectToApplication: aClass controller: '' - ] - - redirectToApplication: aClass controller: aString [ - "Abort all other request handling. - Redirect to the controller named of " - - - self redirectTo: - (self context urlBuilder urlFor: aClass path, '/', aString) - greaseString - ] - - redirectToCurrentController [ - "Abort all other request handling. - Redirect to the current controller method" - - self redirectTo: - (self context urlBuilder urlFor: self router route pathString) - greaseString - ] - - respondOn: aResponse [ - - self build respondOn: aResponse - ] - - printHtmlString [ - - ^String streamContents: [:str | - self build printHtmlOn: str] - ] - - withChildrenRegistrationDo: aBlock [ - - ILCurrentBuildable value ifNotNil: [:parent | - parent registerChild: self]. - ILCurrentBuildable use: self during: aBlock - ] -] diff --git a/iliad-stable/Core/Buildables/ILConfirmationWidget.st b/iliad-stable/Core/Buildables/ILConfirmationWidget.st deleted file mode 100644 index ff69794..0000000 --- a/iliad-stable/Core/Buildables/ILConfirmationWidget.st +++ /dev/null @@ -1,67 +0,0 @@ -"====================================================================== -| -| Iliad.ILConfirmationWidget class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2010 -| Nicolas Petton , -| Sébastien Audier -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - - -ILWidget subclass: ILConfirmationWidget [ - | confirmationString | - - - - - confirmationString [ - - ^confirmationString - ] - - confirmationString: aString [ - - confirmationString := aString - ] - - contents [ - - ^[:e | - e text: self confirmationString. - e form build: [:form | - form button - action: [self answer: true]; - text: 'Yes'. - form button - action: [self answer: false]; - text: 'No']] - ] -] diff --git a/iliad-stable/Core/Buildables/ILCurrentBuildable.st b/iliad-stable/Core/Buildables/ILCurrentBuildable.st deleted file mode 100644 index 4fa108d..0000000 --- a/iliad-stable/Core/Buildables/ILCurrentBuildable.st +++ /dev/null @@ -1,43 +0,0 @@ -"====================================================================== -| -| Iliad.ILCurrentBuildable class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILDynamicVariable subclass: ILCurrentBuildable [ - - -] - diff --git a/iliad-stable/Core/Buildables/ILDecorator.st b/iliad-stable/Core/Buildables/ILDecorator.st deleted file mode 100644 index 755d7a6..0000000 --- a/iliad-stable/Core/Buildables/ILDecorator.st +++ /dev/null @@ -1,116 +0,0 @@ -"====================================================================== -| -| Iliad.ILDecorator class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Some parts of this file reuse code from the Seaside framework written -| by Avi Bryant, Julian Fitzell, Lukas Renggli, Michel Bany, Philippe -| Marschall and Seaside contributors http://www.seaside.st -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILBuildable subclass: ILDecorator [ - | decoratee | - - - - - ILDecorator class >> decoratee: aDecoratee [ - - ^self basicNew - decoratee: aDecoratee; - initialize; - yourself - ] - - decoratee [ - - ^decoratee - ] - - decoratee: aDecoratee [ - - decoratee := aDecoratee - ] - - widget [ - - ^self decoratee widget - ] - - contents [ - - ^self decoratee contents - ] - - updateHead: aHead [ - - self decoratee updateHead: aHead - ] - - styles [ - - ^#() - ] - - scripts [ - - ^#() - ] - - handleAnswer: anAnswer [ - - ^self decoratee handleAnswer: anAnswer - ] - - removeDecorator: aDecorator [ - - self decoratee removeDecorator: aDecorator - ] - - removeYourself [ - - self decoratee removeDecorator: self - ] - - isDelegator [ - - ^false - ] - - isGlobal [ - - ^false - ] -] diff --git a/iliad-stable/Core/Buildables/ILDelegator.st b/iliad-stable/Core/Buildables/ILDelegator.st deleted file mode 100644 index fc4e5b6..0000000 --- a/iliad-stable/Core/Buildables/ILDelegator.st +++ /dev/null @@ -1,87 +0,0 @@ -"====================================================================== -| -| Iliad.ILDelegator class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Some parts of this file reuse code from the Seaside framework written -| by Avi Bryant, Julian Fitzell, Lukas Renggli, Michel Bany, Philippe -| Marschall and Seaside contributors http://www.seaside.st -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILDecorator subclass: ILDelegator [ - | widget | - - - - - widget [ - - ^widget - ] - - widget: aWidget [ - - widget := aWidget - ] - - newRootElement [ - - ^self widget newRootElement - ] - - contents [ - - ^self widget - ] - - updateHead: aHead [ - - self widget updateHead: aHead - ] - - handleAnswer: anAnswer [ - - self widget handleAnswer: anAnswer - ] - - isDelegator [ - - ^true - ] - - isGlobal [ - - ^true - ] -] diff --git a/iliad-stable/Core/Buildables/ILHTMLPage.st b/iliad-stable/Core/Buildables/ILHTMLPage.st deleted file mode 100644 index febb839..0000000 --- a/iliad-stable/Core/Buildables/ILHTMLPage.st +++ /dev/null @@ -1,66 +0,0 @@ -"====================================================================== -| -| Iliad.ILHTMLPage class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILBuildable subclass: ILHTMLPage [ - - - - - body [ - - ^self attributeAt: #body ifAbsentPut: [ILBodyElement new] - ] - - head [ - - ^self attributeAt: #head ifAbsentPut: [ILHeadElement new] - ] - - html [ - - ^self attributeAt: #html ifAbsentPut: [ILHtmlElement new] - ] - - build [ - - ^self html - add: self head; - add: self body; - yourself - ] -] - diff --git a/iliad-stable/Core/Buildables/ILInformationWidget.st b/iliad-stable/Core/Buildables/ILInformationWidget.st deleted file mode 100644 index e092153..0000000 --- a/iliad-stable/Core/Buildables/ILInformationWidget.st +++ /dev/null @@ -1,63 +0,0 @@ -"====================================================================== -| -| Iliad.ILInformationWidget class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2010 -| Nicolas Petton , -| Sébastien Audier -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - - -ILWidget subclass: ILInformationWidget [ - | informationString | - - - - - informationString [ - - ^informationString - ] - - informationString: aString [ - - informationString := aString - ] - - contents [ - - ^[:e | - e text: self informationString. - e form button - action: [self answer]; - text: 'Ok'] - ] -] diff --git a/iliad-stable/Core/Buildables/ILPluggableWidget.st b/iliad-stable/Core/Buildables/ILPluggableWidget.st deleted file mode 100644 index 4e61900..0000000 --- a/iliad-stable/Core/Buildables/ILPluggableWidget.st +++ /dev/null @@ -1,58 +0,0 @@ -"====================================================================== -| -| Iliad.ILPluggableWidget class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - -ILWidget subclass: ILPluggableWidget [ - | contentsBlock | - - - - - contentsBlock [ - - ^contentsBlock ifNil: [[:e | ]] - ] - - contentsBlock: aBlock [ - - contentsBlock := aBlock - ] - - contents [ - - ^self contentsBlock - ] -] - diff --git a/iliad-stable/Core/Buildables/ILPrependDelegator.st b/iliad-stable/Core/Buildables/ILPrependDelegator.st deleted file mode 100644 index e472eb0..0000000 --- a/iliad-stable/Core/Buildables/ILPrependDelegator.st +++ /dev/null @@ -1,53 +0,0 @@ -"====================================================================== -| -| Iliad.ILPrependDelegator class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2009 -| Nicolas Petton , -| Sébastien Audier -| -| Some parts of this file reuse code from the Seaside framework written -| by Avi Bryant, Julian Fitzell, Lukas Renggli, Michel Bany, Philippe -| Marschall and Seaside contributors http://www.seaside.st -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILDelegator subclass: ILPrependDelegator [ - - - - - contents [ - - ^[:e | e - build: super contents; - build: self decoratee contents] - ] -] diff --git a/iliad-stable/Core/Buildables/ILProfiler.st b/iliad-stable/Core/Buildables/ILProfiler.st deleted file mode 100644 index e3c49fd..0000000 --- a/iliad-stable/Core/Buildables/ILProfiler.st +++ /dev/null @@ -1,85 +0,0 @@ -"====================================================================== -| -| Iliad.ILProfiler class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2010 -| Nicolas Petton , -| Sébastien Audier -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILDecorator subclass: ILProfiler [ - - - - - contents [ - - ^[:e | - Transcript - show: '-- Iliad Profiler on: ', self widget greaseString , ' --'; - cr. - [e build: self decoratee contents] profile do: [:each | - Transcript show: each greaseString; cr]. - ] - ] -] - -BlockClosure extend [ - - profile [ - - | results workProcess finished s profProcess | - s := Semaphore new. - results := IdentityBag new. - workProcess := Processor activeProcess. - finished := false. - profProcess := [ - [(Delay forMilliseconds: 2) wait. - finished] whileFalse: [ - results add: workProcess suspendedContext method]. - s signal] - forkAt: Processor highIOPriority. - self ensure: [ - finished := true. - s wait. - ^results sortedByCount] - ] -] - -Bag subclass: IdentityBag [ - - - - dictionaryClass [ - ^IdentityDictionary - ] -] - diff --git a/iliad-stable/Core/Buildables/ILSequence.st b/iliad-stable/Core/Buildables/ILSequence.st deleted file mode 100644 index d2f5393..0000000 --- a/iliad-stable/Core/Buildables/ILSequence.st +++ /dev/null @@ -1,72 +0,0 @@ -"====================================================================== -| -| Iliad.ILSequence class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2010 -| Nicolas Petton , -| Sébastien Audier -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - - -ILWidget subclass: ILSequence [ - - - - - build [ - - self shouldStart ifTrue: [self start]. - ^super build - ] - - contents [ - - "Do not override. The purpose of a sequence is to display other buildables" - self shouldNotImplement - ] - - start [ - - "Override this method in subclasses" - ] - - restart [ - - self - retrieveControl; - markDirty - ] - - shouldStart [ - - ^decorator widget = self - ] -] diff --git a/iliad-stable/Core/Buildables/ILWidget.st b/iliad-stable/Core/Buildables/ILWidget.st deleted file mode 100644 index d5b1b8b..0000000 --- a/iliad-stable/Core/Buildables/ILWidget.st +++ /dev/null @@ -1,460 +0,0 @@ -"====================================================================== -| -| Iliad.ILWidget class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Some parts of this file reuse code from the Seaside framework written -| by Avi Bryant, Julian Fitzell, Lukas Renggli, Michel Bany, Philippe -| Marschall and Seaside contributors http://www.seaside.st -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILBuildable subclass: ILWidget [ - | id state decorator owner dependentWidgets | - - - - - initialize [ - - super initialize. - decorator := ILDecorator decoratee: self. - dependentWidgets := OrderedCollection new. - ] - - postCopy [ - - super postCopy. - decorator := ILDecorator decoratee: self. - dependentWidgets := OrderedCollection new. - state := nil. - id := nil - ] - - state [ - - ^state copy - ] - - id: aString [ - - id := aString - ] - - id [ - - ^id ifNil: [id := self session nextId] - ] - - owner: aWidget [ - - owner := aWidget - ] - - owner [ - "Answer the widget which shows me. if any" - - - ^owner - ] - - dependentWidgets [ - - ^dependentWidgets copy - ] - - widget [ - - ^self - ] - - widgetFor: aBuildable [ - "Convenience method. This is useful for building anonymous widgets. - ex: myWidget := self widgetFor: [:e | e h1: 'Hello world!']" - - - ^ILPluggableWidget new - contentsBlock: aBuildable; - yourself - ] - - stateRegistry [ - - ^self context stateRegistry - ] - - buildContents [ - "Do *not* override this method. Use #contents instead" - - - self registerState. - self context addBuiltWidget: self. - - ^self newRootElement - class: self id; - build: self fullContents; - yourself - ] - - fullContents [ - "Do *not* override this method. Use #contents instead" - - ^decorator contents - ] - - buildHead: aHead [ - - decorator updateHead: aHead - ] - - contents [ - "Override this method to add contents to your widget" - - - ^[:e | ] - ] - - scripts [ - "Answer a collection of strings. - Override in subclasses to add scripts to load with the widget" - - - ^#() - ] - - styles [ - "Answer a collection of strings. - Override in subclasses to add styles to load with the widget" - - - ^#() - ] - - decorateWith: aDecorator [ - - | dec1 dec2 | - dec1 := nil. - dec2 := decorator. - [dec2 = self or: [ - aDecorator isGlobal]] whileFalse: [ - dec1 := dec2. - dec2 := dec2 decoratee]. - aDecorator decoratee: dec2. - dec1 isNil - ifTrue: [decorator := aDecorator] - ifFalse: [dec1 decoratee: aDecorator] - ] - - decorateWith: aDecorator during: aBlock [ - - self decorateWith: aDecorator. - aBlock value. - aDecorator removeYourself - ] - - decoratorsDo: aBlock [ - - | dec | - dec := decorator. - [dec ~= self] whileTrue: [ - aBlock value: dec. - dec := dec decoratee] - ] - - withDecoratorsDo: aBlock [ - - aBlock value: self. - self decoratorsDo: aBlock - ] - - removeDecorator: aDecorator [ - "Remove from the decoration chain, - except if is the initial one" - - - decorator = aDecorator - ifTrue: [ - decorator decoratee = self ifFalse: [ - decorator := aDecorator decoratee]] - ifFalse: [| dec1 dec2 | - dec1 := decorator. - [dec1 = aDecorator] whileFalse: [ - dec2 := dec1. - dec1 := dec1 decoratee]. - dec2 decoratee: dec1 decoratee] - ] - - rootElementClass [ - - ^ILDivElement - ] - - answer [ - "Give the control back to the owner, i.e, the widget which showed the receiver. - Answer self" - - - ^self answer: self - ] - - answer: anAnswer [ - "Give the control back to the owner, i.e, the widget which showed the receiver. - Answer " - - - decorator handleAnswer: anAnswer - ] - - handleAnswer: anAnswer [ - - ^nil - ] - - retrieveControl [ - "Give the control back to the receiver, and make any showed widget answer nil" - - - self decoratorsDo: [:each | - each isDelegator ifTrue: [ - each widget answer: nil]] - ] - - show: aWidget [ - "Show another widget instead of the receiver. - The receiver is also implicitely marked dirty" - - - self show: aWidget onAnswer: [:ans | ] - ] - - show: aWidget onAnswer: aBlock [ - "Show another widget instead of the receiver and catch the answer in . - The receiver is also implicitely marked dirty" - - - self - show: aWidget - onAnswer: aBlock - delegator: (ILDelegator new widget: aWidget) - ] - - append: aWidget [ - "Insert after the receiver" - - - self append: aWidget onAnswer: [:ans |] - ] - - append: aWidget onAnswer: aBlock [ - "Insert after the receiver" - - - self - show: aWidget - onAnswer: aBlock - delegator: (ILAppendDelegator new widget: aWidget) - ] - - prepend: aWidget [ - "Insert before the receiver" - - - self prepend: aWidget onAnswer: [:ans |] - ] - - prepend: aWidget onAnswer: aBlock [ - "Insert before the receiver" - - - self - show: aWidget - onAnswer: aBlock - delegator: (ILPrependDelegator new widget: aWidget) - ] - - show: aWidget onAnswer: aBlock delegator: aDelegator [ - - | answerHandler | - answerHandler := ILAnswerHandler new. - self - decorateWith: aDelegator; - markDirty. - answerHandler action: (self session actionFor: [:value | - aDelegator removeYourself. - self markDirty. - aWidget owner: nil. - answerHandler removeYourself. - aBlock value: value]). - aWidget - owner: self; - decorateWith: answerHandler - ] - - inform: aString [ - - self show: (ILInformationWidget new - informationString: aString; - yourself) - ] - - confirm: aString ifTrue: aBlock [ - - self - confirm: aString - ifTrue: aBlock - ifFalse: [] - ] - - confirm: aString ifTrue: aBlock ifFalse: anotherBlock [ - - self - show: (ILConfirmationWidget new - confirmationString: aString; - yourself) - onAnswer: [:boolean | - boolean ifTrue: aBlock ifFalse: anotherBlock] - ] - - addDependentWidget: aWidget [ - "Add to my dependent widgets. - Each dependent widget will be rebuilt on AJAX requests whenever - I am rebuilt" - - - (dependentWidgets includes: aWidget) ifFalse: [ - dependentWidgets add: aWidget] - ] - - removeDependentWidget: aWidget [ - - (dependentWidgets includes: aWidget) ifTrue: [ - dependentWidgets remove: aWidget] - ] - - registerState [ - - self stateRegistry register: self - ] - - markDirty [ - "Mark the receiver as 'dirty', - so the widget will be rebuilt on Ajax requests. - You do not need to mark subwidgets as dirty, - they will be rebuilt together with the receiver" - - - self owner - ifNil: [self beDirty] - ifNotNil: [self owner markDirty]. - dependentWidgets do: [:each | each markDirty] - ] - - printJsonOn: aStream [ - - self build printJsonOn: aStream - ] - - newRootElement [ - - ^self rootElementClass new - ] - - updateHead: aHead [ - - self withDecoratorsDo: [:each | - each scripts do: [:script || e | - e := ILHTMLBuilderElement new javascript src: script. - (aHead children includes: e) ifFalse: [ - aHead add: e]]. - each styles do: [:script || e | - e := ILHTMLBuilderElement new stylesheet href: script. - (aHead children includes: e) ifFalse: [ - aHead add: e]]] - ] - - beDirty [ - - state := self session nextId - ] -] diff --git a/iliad-stable/Core/Dispatching/ILDispatchError.st b/iliad-stable/Core/Dispatching/ILDispatchError.st deleted file mode 100644 index 033ce71..0000000 --- a/iliad-stable/Core/Dispatching/ILDispatchError.st +++ /dev/null @@ -1,47 +0,0 @@ -"====================================================================== -| -| Iliad.ILDispatchError class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Some parts of this file reuse code from the Seaside framework written -| by Avi Bryant, Julian Fitzell, Lukas Renggli, Michel Bany, Philippe -| Marschall and Seaside contributors http://www.seaside.st -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -Grease.GRError subclass: ILDispatchError [ - - - -] - diff --git a/iliad-stable/Core/Dispatching/ILDispatcher.st b/iliad-stable/Core/Dispatching/ILDispatcher.st deleted file mode 100644 index dad731e..0000000 --- a/iliad-stable/Core/Dispatching/ILDispatcher.st +++ /dev/null @@ -1,110 +0,0 @@ -"====================================================================== -| -| Iliad.ILDispatcher class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILObject subclass: ILDispatcher [ - - - >current - to handle requests, -and wait for a ILResponseNotification to respond to them.'> - - ILDispatcher class [ - | current | - - current [ - - ^current ifNil: [current := super new] - ] - - new [ - - self shouldNotImplement - ] - ] - - dispatch: aRequest [ - "Entry point of requests" - - - self withErrorHandling: [ - ILCurrentContext - use: (self createContextFor: aRequest) - during: [ - self withDispatchErrorHandling: [ - self context router dispatchRequest]]] - ] - - withDispatchErrorHandling: aBlock [ - "Catch dispatch errors" - - - aBlock - on: ILDispatchError - do: [:error | - ILNotFoundHandler new handleRequest] - ] - - withErrorHandling: aBlock [ - "Catch errors and use an ILErrorHandler to handle them" - - - aBlock - on: Error - do: [:error | - ILErrorHandler new - error: error; - handleRequest] - ] - - createContextFor: aRequest [ - - ^ILContext new - request: aRequest; - session: (self findSessionFor: aRequest); - yourself - ] - - findSessionFor: aRequest [ - - ^ILSessionManager current sessionFor: aRequest - ] -] diff --git a/iliad-stable/Core/Dispatching/ILRoute.st b/iliad-stable/Core/Dispatching/ILRoute.st deleted file mode 100644 index 837048c..0000000 --- a/iliad-stable/Core/Dispatching/ILRoute.st +++ /dev/null @@ -1,155 +0,0 @@ -"====================================================================== -| -| Iliad.ILRoute class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILObject subclass: ILRoute [ - | path stream | - - - protocol.'> - - ILRoute class >> delimiters [ - - ^Array with: $/ - ] - - ILRoute class >> path: aCollection [ - - ^self basicNew - initializeWithPath: aCollection; - yourself - ] - - basePath [ - - self path isEmpty ifTrue: [^'/']. - ^'/' , self path first - ] - - delimiter [ - - ^self delimiters first - ] - - delimiters [ - - ^self class delimiters - ] - - path [ - - ^path ifNil: [path := OrderedCollection new] - ] - - initializeWithPath: aCollection [ - - path := aCollection. - stream := ReadStream on: path - ] - - currentPath [ - "Return an absolute url of the current streamed path - separated with delimiters, like this: - /foo/bar/baz" - - - | part | - ^String streamContents: [:s | - 1 to: stream position do: [:i | - part := path at: i. - s nextPut: $/; nextPutAll: part]] - ] - - atEnd [ - - ^stream atEnd - ] - - next [ - - ^stream atEnd - ifTrue: [nil] - ifFalse: [stream next] - ] - - peek [ - - ^stream peek - ] - - position [ - - ^stream position - ] - - position: anInteger [ - - stream position: anInteger - ] - - reset [ - - stream reset - ] - - pathString [ - - | str | - str := WriteStream on: String new. - str nextPut: $/. - self path - do: [:each | str nextPutAll: each] - separatedBy: [str nextPut: self delimiter]. - ^str contents - ] - - uriString [ - - ^self pathString - ] - - printOn: aStream [ - - super printOn: aStream. - aStream - nextPut: Character space; - nextPutAll: self uriString - ] -] - diff --git a/iliad-stable/Core/Dispatching/ILRouter.st b/iliad-stable/Core/Dispatching/ILRouter.st deleted file mode 100644 index 28fd8b3..0000000 --- a/iliad-stable/Core/Dispatching/ILRouter.st +++ /dev/null @@ -1,131 +0,0 @@ -"====================================================================== -| -| Iliad.ILRouter class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILObject subclass: ILRouter [ - | route hashRoute application controller | - - - - - initialize [ - - super initialize. - self - setApplication; - setRoutePosition; - setController; - updateApplicationFromRoute - ] - - dispatchRequest [ - - self shouldRedirect ifTrue: [ - ILRedirectHandler new handleRequest]. - self application - ifNil: [ILFileHandler new handleRequest] - ifNotNil: [ILApplicationHandler new handleRequest] - ] - - route [ - - ^route ifNil: [route := ILRoute path: self request url path] - ] - - hashRoute [ - - | hash | - hash := self request hashLocationField ifNil: ['']. - ^hashRoute ifNil: [hashRoute := ILRoute path: (hash tokenize: '/')] - ] - - application [ - - ^application - ] - - controller [ - - ^controller - ] - - shouldRedirect [ - - self request isTypeOfRequestForJson ifTrue: [^false]. - ^self request sessionField notNil and: [self request hasCookies] - ] - - setApplication [ - - application := self applicationClass - ifNotNil: [:applicationClass | - self session applications - at: applicationClass - ifAbsentPut: [applicationClass new]] - ] - - setRoutePosition [ - - self application ifNotNil: [ - self route position: - (ILUrl absolute: self application class path) path size] - ] - - setController [ - - self route atEnd ifFalse: [ - controller := self route next] - ] - - applicationClass [ - - | applicationClass | - applicationClass := nil. - [self route atEnd not] whileTrue: [ - self route next. - applicationClass := ILApplication allSubclasses - detect: [:each | each absolutePath = self route currentPath] - ifNone: [applicationClass]]. - ^applicationClass - ] - - updateApplicationFromRoute [ - - self application ifNotNil: [ - self application updateFromRoute: self route] - ] -] diff --git a/iliad-stable/Core/Elements/Extensions.st b/iliad-stable/Core/Elements/Extensions.st deleted file mode 100644 index d02d1d9..0000000 --- a/iliad-stable/Core/Elements/Extensions.st +++ /dev/null @@ -1,12 +0,0 @@ -Object extend [ - - printHtmlOn: aStream [ - - self displayOn: aStream - ] - - printEncodedOn: aStream [ - - Iliad.ILEncoder encodeForHTTP: self greaseString on: aStream - ] -] diff --git a/iliad-stable/Core/Elements/ILElement.st b/iliad-stable/Core/Elements/ILElement.st deleted file mode 100644 index 26c98a2..0000000 --- a/iliad-stable/Core/Elements/ILElement.st +++ /dev/null @@ -1,177 +0,0 @@ -"====================================================================== -| -| Iliad.ILElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILComposite subclass: ILElement [ - | attributes | - - - - - - = anObject [ - - ^super = anObject and: [ - self attributes = anObject attributes] - ] - - hash [ - - ^super hash bitXor: self attributes hash - ] - - attributes [ - - ^attributes ifNil: [attributes := Grease.GRSmallDictionary new] - ] - - attributeAt: akey [ - - ^self attributes at: akey ifAbsent: [nil] - ] - - attributeAt: akey ifAbsent: aBlock [ - - ^self attributes at: akey ifAbsent: aBlock - ] - - attributeAt: akey ifAbsentPut: aBlock [ - - ^self attributes at: akey ifAbsentPut: aBlock - ] - - attributeAt: aKey put: aValue [ - - ^self attributes at: aKey put: aValue - ] - - contentType [ - - self subclassResponsibility - ] - - tag [ - - ^nil - ] - - printJsonOn: aStream [ - - | str | - str := WriteStream on: String new. - self printHtmlOn: str. - str contents printJsonOn: aStream - ] - - printHtmlOn: aStream [ - - self beforePrintHtml. - self printOpenTagOn: aStream. - self childrenDo: [:each | - each printHtmlOn: aStream]. - self printCloseTagOn: aStream. - self afterPrintHtml - ] - - afterPrintHtml [ - - ] - - beforePrintHtml [ - - ] - - printAttribute: anAttribute on: aStream [ - - aStream - nextPut: Character space; - nextPutAll: anAttribute key; - nextPutAll: '="'. - anAttribute value printEncodedOn: aStream. - aStream nextPut: $" - ] - - printCloseTagOn: aStream [ - - self tag ifNotNil: [aStream nextPutAll: ''] - ] - - printOpenTagOn: aStream [ - - self tag ifNotNil: [ - aStream nextPutAll: '<' , self tag. - self attributes associationsDo: [:each | - each value ifNotNil: [ - self printAttribute: each on: aStream]]. - aStream nextPutAll: '>'] - ] - - build: aBuildable [ - - aBuildable buildOn: self - ] - - text: aString [ - - ^self add: (ILTextElement new - contents: aString; - yourself) - ] - - xml [ - - ^self add: ILXmlElement new - ] - - attributeError: key [ - - ILAttributeError signal: key - ] - - doesNotUnderstandAttribute: aString [ - - ^(AttributeNotUnderstood element: self attribute: aString) signal - ] - - respondOn: aResponse [ - - self printHtmlOn: aResponse. - aResponse contentType: self contentType - ] -] diff --git a/iliad-stable/Core/Elements/ILElements-Error.st b/iliad-stable/Core/Elements/ILElements-Error.st deleted file mode 100644 index ead67e4..0000000 --- a/iliad-stable/Core/Elements/ILElements-Error.st +++ /dev/null @@ -1,68 +0,0 @@ -Grease.GRError subclass: ILAttributeError [ - - - -] - - - -Grease.GRError subclass: ILAttributeNotUnderstood [ - | element attribute | - - - - - ILAttributeNotUnderstood class >> element: anElement attribute: aString [ - - ^(self new) - element: anElement; - attribute: aString; - yourself - ] - - attribute [ - - ^attribute - ] - - attribute: anObject [ - - attribute := anObject - ] - - element [ - - ^element - ] - - element: anElement [ - - element := anElement - ] - - defaultAction [ - - - ] - - isResumable [ - - ^true - ] - - messageText [ - - ^'Tag ''{1}'' does not understand attribute ''{2}''' format: - {self element tag. - self attribute} - ] -] - - - -Grease.GRError subclass: ILElementError [ - - - -] - diff --git a/iliad-stable/Core/Elements/ILTextElement.st b/iliad-stable/Core/Elements/ILTextElement.st deleted file mode 100644 index cbe7b9b..0000000 --- a/iliad-stable/Core/Elements/ILTextElement.st +++ /dev/null @@ -1,82 +0,0 @@ -"====================================================================== -| -| Iliad.ILTextElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILElement subclass: ILTextElement [ - | contents tag | - - - - - add: anElement [ - - ILElementError signal: 'Can''t add an element to a ' , self class name - ] - - text: aString [ - - self contents: aString - ] - - contents [ - - ^contents ifNil: [contents := String new] - ] - - contents: aString [ - - contents := aString - ] - - tag [ - - ^tag - ] - - tag: aString [ - - tag := aString - ] - - printHtmlOn: aStream [ - - self printOpenTagOn: aStream. - ILEncoder encodeForHTTP: self contents on: aStream. - self printCloseTagOn: aStream - ] -] - diff --git a/iliad-stable/Core/Elements/ILXmlElement.st b/iliad-stable/Core/Elements/ILXmlElement.st deleted file mode 100644 index 2ec41bd..0000000 --- a/iliad-stable/Core/Elements/ILXmlElement.st +++ /dev/null @@ -1,71 +0,0 @@ -"====================================================================== -| -| Iliad.ILXmlElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILElement subclass: ILXmlElement [ - | tag | - - - - - contentType [ - - ^'text/xml; charset=', self session charset - ] - - xmlTag [ - - ^'' - ] - - tag [ - - ^tag - ] - - tag: aString [ - - tag := aString - ] - - respondOn: aResponse [ - - aResponse nextPutAll: self xmlTag. - super respondOn: aResponse - ] -] - diff --git a/iliad-stable/Core/GST/Extensions.st b/iliad-stable/Core/GST/Extensions.st deleted file mode 100644 index fc3aca6..0000000 --- a/iliad-stable/Core/GST/Extensions.st +++ /dev/null @@ -1,12 +0,0 @@ -Grease.GRGSTPlatform extend [ - - asMethodReturningString: aByteArrayOrString named: aSymbol [ - "Generates the source of a method named aSymbol that returns aByteArrayOrString as a String" - - ^String streamContents: [ :stream | - stream nextPutAll: aSymbol; nextPutAll: ' [ '; nl. - stream tab; nextPutAll: ' ^'. - aByteArrayOrString storeLiteralOn: stream. - stream nl; nextPutAll: ']' ] - ] -] diff --git a/iliad-stable/Core/GST/ILDiskDirectory.st b/iliad-stable/Core/GST/ILDiskDirectory.st deleted file mode 100644 index b7b0e82..0000000 --- a/iliad-stable/Core/GST/ILDiskDirectory.st +++ /dev/null @@ -1,49 +0,0 @@ -ILDirectory subclass: ILDiskDirectory [ - | directory | - - - - - fileContentsFor: aString [ - - | file stream | - file := self fileNamed: (self adjustPath: aString). - file isNil ifTrue: [^nil]. - stream := file readStream. - ^[stream contents] ensure: [stream close] - ] - - directory [ - - ^directory - ] - - directory: aDirectory [ - - directory := aDirectory - ] - - fileNamed: aFilename [ - "Try to find a file named in the directory" - - - | file | - aFilename isEmpty ifTrue: [^nil]. - file := self directory / aFilename. - (file notNil and: [file exists]) ifTrue: [^file]. - ^nil - ] - - adjustPath: aFilename [ - - ^aFilename copyReplacingRegex: '^\/' with: '' - ] -] diff --git a/iliad-stable/Core/HTMLElements/ILAnchorElement.st b/iliad-stable/Core/HTMLElements/ILAnchorElement.st deleted file mode 100644 index 46d9604..0000000 --- a/iliad-stable/Core/HTMLElements/ILAnchorElement.st +++ /dev/null @@ -1,99 +0,0 @@ -"====================================================================== -| -| Iliad.ILAnchorElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILLinkableElement subclass: ILAnchorElement [ - - - - - action: aBlock [ - - self action: aBlock hash: '' - ] - - action: aBlock hash: aString [ - - - | action | - action := self session registerActionFor: aBlock. - self href: (self context urlBuilder - urlForAction: action - hash: aString) - ] - - tag [ - - ^'a' - ] - - tabindex: anInteger [ - - self attributeAt: 'tabindex' put: anInteger greaseString - ] - - circleShape [ - - self shape: 'circle' - ] - - coords: aString [ - - self attributeAt: 'coords' put: aString - ] - - defaultShape [ - - self shape: 'default' - ] - - polyShape [ - - self shape: 'poly' - ] - - rectShape [ - - self shape: 'rect' - ] - - shape: aString [ - - self attributeAt: 'shape' put: aString - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILAreaElement.st b/iliad-stable/Core/HTMLElements/ILAreaElement.st deleted file mode 100644 index b6cff41..0000000 --- a/iliad-stable/Core/HTMLElements/ILAreaElement.st +++ /dev/null @@ -1,103 +0,0 @@ -"====================================================================== -| -| Iliad.ILAreaElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - -ILClosingElement subclass: ILAreaElement [ - - - - - tag [ - - ^'area' - ] - - accesskey: aCharacter [ - - self attributeAt: 'accesskey' put: aCharacter greaseString - ] - - alt: aString [ - - self attributeAt: 'alt' put: aString - ] - - href: aString [ - - self attributeAt: 'href' put: aString - ] - - nohref [ - - self attributeAt: 'nohref' put: 'nohref' - ] - - tabindex: anInteger [ - - self attributeAt: 'tabindex' put: anInteger greaseString - ] - - circleShape [ - - self shape: 'circle' - ] - - coords: aString [ - - self attributeAt: 'coords' put: aString - ] - - defaultShape [ - - self shape: 'default' - ] - - polyShape [ - - self shape: 'poly' - ] - - rectShape [ - - self shape: 'rect' - ] - - shape: aString [ - - self attributeAt: 'shape' put: aString - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILBodyElement.st b/iliad-stable/Core/HTMLElements/ILBodyElement.st deleted file mode 100644 index dd6c972..0000000 --- a/iliad-stable/Core/HTMLElements/ILBodyElement.st +++ /dev/null @@ -1,59 +0,0 @@ -"====================================================================== -| -| Iliad.ILBodyElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILHTMLBuilderElement subclass: ILBodyElement [ - - - - - tag [ - - ^'body' - ] - - onLoad: aString [ - - self onEvent: 'Load' add: aString - ] - - onUnload: aString [ - - self onEvent: 'Unload' add: aString - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILBreakElement.st b/iliad-stable/Core/HTMLElements/ILBreakElement.st deleted file mode 100644 index 34e4a92..0000000 --- a/iliad-stable/Core/HTMLElements/ILBreakElement.st +++ /dev/null @@ -1,53 +0,0 @@ -"====================================================================== -| -| Iliad.ILBreakElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILClosingElement subclass: ILBreakElement [ - - - - - tag [ - - ^'br' - ] - - onEvent: event add: aString [ - - self doesNotUnderstandAttribute: 'on' , event - ] -] diff --git a/iliad-stable/Core/HTMLElements/ILButtonElement.st b/iliad-stable/Core/HTMLElements/ILButtonElement.st deleted file mode 100644 index 20393ac..0000000 --- a/iliad-stable/Core/HTMLElements/ILButtonElement.st +++ /dev/null @@ -1,79 +0,0 @@ -"====================================================================== -| -| Iliad.ILButtonElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILFormElementElement subclass: ILButtonElement [ - - - - - tag [ - - ^'button' - ] - - beButton [ - - self type: 'button' - ] - - beReset [ - - self type: 'reset' - ] - - beSubmit [ - - self type: 'submit' - ] - - type: aString [ - - self attributeAt: 'type' put: aString - ] - - value: aString [ - - self attributeAt: 'value' put: aString - ] - - beforePrintHtml [ - - self attributeAt: 'type' ifAbsentPut: ['submit'] - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILCheckboxElement.st b/iliad-stable/Core/HTMLElements/ILCheckboxElement.st deleted file mode 100644 index 7358d3d..0000000 --- a/iliad-stable/Core/HTMLElements/ILCheckboxElement.st +++ /dev/null @@ -1,82 +0,0 @@ -"====================================================================== -| -| Iliad.ILCheckboxElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILFormElementElement subclass: ILCheckboxElement [ - | value hiddenAction | - - - - - tag [ - - ^'input' - ] - - action: aBlock [ - - | action | - hiddenAction := aBlock. - value := false. - action := self session registerActionFor: [:val | value := true]. - self name: action key. - self addHiddenInput - ] - - beChecked [ - - self checked: true - ] - - checked: aBoolean [ - - aBoolean ifTrue: [self attributeAt: 'checked' put: 'checked'] - ] - - beforePrintHtml [ - - self attributeAt: 'type' put: 'checkbox' - ] - - addHiddenInput [ - - self input - beHidden; - action: [:val | hiddenAction value: value. value := false] - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILClosingElement.st b/iliad-stable/Core/HTMLElements/ILClosingElement.st deleted file mode 100644 index c20f8dc..0000000 --- a/iliad-stable/Core/HTMLElements/ILClosingElement.st +++ /dev/null @@ -1,52 +0,0 @@ -"====================================================================== -| -| Iliad.ILClosingElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILHTMLBuilderElement subclass: ILClosingElement [ - - - - - printHtmlOn: aStream [ - - aStream nextPutAll: '<' , self tag. - self attributes - associationsDo: [:each | self printAttribute: each on: aStream]. - aStream nextPutAll: '/>' - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILConditionalCommentElement.st b/iliad-stable/Core/HTMLElements/ILConditionalCommentElement.st deleted file mode 100644 index 236dc27..0000000 --- a/iliad-stable/Core/HTMLElements/ILConditionalCommentElement.st +++ /dev/null @@ -1,124 +0,0 @@ -"====================================================================== -| -| Iliad.ILConditionalCommentElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILHTMLBuilderElement subclass: ILConditionalCommentElement [ - | conditions | - - - - printOpenTagOn: aStream [ - - aStream nextPutAll: '' - ] - - conditions [ - - ^conditions ifNil: [conditions := OrderedCollection new] - ] - - ie [ - - self conditions add: 'IE' - ] - - ie5 [ - - self conditions add: 'IE 5' - ] - - ie50 [ - - self conditions add: 'IE 5.0' - ] - - ie55 [ - - self conditions add: 'IE 5.5' - ] - - ie6 [ - - self conditions add: 'IE 6' - ] - - ie7 [ - - self conditions add: 'IE 7' - ] - - ie8 [ - - self conditions add: 'IE 8' - ] - - gt [ - "Greater than" - - - self conditions add: 'gt' - ] - - lt [ - "Less than" - - - self conditions add: 'lt' - ] - - not [ - "Not" - - - self conditions add: '!' - ] - - onEvent: event add: aString [ - - self doesNotUnderstandAttribute: 'on' , event - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILDirectionElement.st b/iliad-stable/Core/HTMLElements/ILDirectionElement.st deleted file mode 100644 index 0535731..0000000 --- a/iliad-stable/Core/HTMLElements/ILDirectionElement.st +++ /dev/null @@ -1,69 +0,0 @@ -"====================================================================== -| -| Iliad.ILDirectionElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILHTMLBuilderElement subclass: ILDirectionElement [ - - - - - tag [ - - ^'bdo' - ] - - xmlLang: aString [ - - self doesNotUnderstandAttribute: 'xml:lang' - ] - - dir: aString [ - - self attributeAt: 'dir' put: aString - ] - - onEvent: event add: aString [ - - self doesNotUnderstandAttribute: 'on' , event - ] - - beforePrintHtml [ - - self attributeAt: 'dir' ifAbsent: [self attributeError: '''dir'' not set'] - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILDivElement.st b/iliad-stable/Core/HTMLElements/ILDivElement.st deleted file mode 100644 index fa64499..0000000 --- a/iliad-stable/Core/HTMLElements/ILDivElement.st +++ /dev/null @@ -1,49 +0,0 @@ -"====================================================================== -| -| Iliad.ILDivElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILHTMLBuilderElement subclass: ILDivElement [ - - - - - tag [ - - ^'div' - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILFieldsetElement.st b/iliad-stable/Core/HTMLElements/ILFieldsetElement.st deleted file mode 100644 index 2aa3356..0000000 --- a/iliad-stable/Core/HTMLElements/ILFieldsetElement.st +++ /dev/null @@ -1,49 +0,0 @@ -"====================================================================== -| -| Iliad.ILFieldsetElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILHTMLBuilderElement subclass: ILFieldsetElement [ - - - - - tag [ - - ^'fieldset' - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILFormElement.st b/iliad-stable/Core/HTMLElements/ILFormElement.st deleted file mode 100644 index 800c3bf..0000000 --- a/iliad-stable/Core/HTMLElements/ILFormElement.st +++ /dev/null @@ -1,174 +0,0 @@ -"====================================================================== -| -| Iliad.ILFormElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILHTMLBuilderElement subclass: ILFormElement [ - - - - - ILFormElement class >> encodingType [ - - ^'application/x-www-form-urlencoded' - ] - - ILFormElement class >> multipartFormData [ - - ^'multipart/form-data' - ] - - tag [ - - ^'form' - ] - - url [ - - ^self context baseUrl greaseString - ] - - accept: aString [ - - self attributeAt: 'accept' put: aString - ] - - acceptCharset: aString [ - - self attributeAt: 'accept-charset' put: aString - ] - - acceptCharsets: aCollection [ - - | encodings | - encodings := WriteStream on: String new. - aCollection do: [:each | encodings nextPutAll: each] - separatedBy: [encodings nextPutAll: ' ']. - self acceptCharset: encodings contents - ] - - accepts: aCollection [ - - | contentTypes | - contentTypes := WriteStream on: String new. - aCollection do: [:each | contentTypes nextPutAll: each] - separatedBy: [contentTypes nextPutAll: ' ']. - self accept: contentTypes contents - ] - - beMultipart [ - - self enctype: self class multipartFormData - ] - - enctype [ - - ^self attributeAt: 'enctype' - ] - - enctype: aString [ - - self attributeAt: 'enctype' put: aString - ] - - multipart: aBoolean [ - - aBoolean ifTrue: - [self beMultipart] - ] - - useGet [ - - self attributeAt: 'method' put: 'get' - ] - - usePost [ - - self attributeAt: 'method' put: 'post' - ] - - onReset: aString [ - - self onEvent: 'reset' add: aString - ] - - onSubmit: aString [ - - self onEvent: 'submit' add: aString - ] - - onResetDo: aBlock [ - - self onEvent: 'reset' do: aBlock - ] - - onSubmitDo: aBlock [ - - self onEvent: 'submit' do: aBlock - ] - - beforePrintHtml [ - - self attributeAt: 'action' ifAbsentPut: [self context baseUrl withoutParameters greaseString]. - self attributeAt: 'method' ifAbsent: [self usePost]. - self attributeAt: 'accept-charset' ifAbsentPut: [self session charset]. - self addHiddenParameters - ] - - isMultipart [ - - ^self enctype = self class multipartFormData - ] - - addHiddenParameters [ - - self context urlBuilder baseUrl parameters keysAndValuesDo: [:key :value | - self input - beHidden; - name: key; - value: value]. - self input - beHidden; - name: self context urlBuilder stateKey; - value: self session stateRegistry key. - self isMultipart ifTrue: [ - self input - beHidden; - name: '_callback'; - value: (self context urlBuilder urlForAction: (self session registerActionFor: [])) greaseString] - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILFormElementElement.st b/iliad-stable/Core/HTMLElements/ILFormElementElement.st deleted file mode 100644 index a44da22..0000000 --- a/iliad-stable/Core/HTMLElements/ILFormElementElement.st +++ /dev/null @@ -1,98 +0,0 @@ -"====================================================================== -| -| Iliad.ILFormElementElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILHTMLBuilderElement subclass: ILFormElementElement [ - - - - - accesskey: aCharacter [ - - self attributeAt: 'accesskey' put: aCharacter greaseString - ] - - action: aBlock [ - - | action | - action := self session registerActionFor: aBlock. - self name: action key - ] - - name [ - - ^self attributeAt: 'name' - ] - - name: aString [ - - self attributeAt: 'name' put: aString - ] - - readonly: aBoolean [ - - self attributeAt: 'readonly' put: aBoolean greaseString - ] - - beSubmitOnChange [ - - self beSubmitOnEvent: 'change' - ] - - beSubmitOnClick [ - - self beSubmitOnEvent: 'click' - ] - - beSubmitOnEvent: aString [ - - self onEvent: aString add: 'iliad.evaluateFormElementAction(this)' - ] - - disabled: aBoolean [ - - aBoolean ifTrue: [ - self attributeAt: 'disabled' put: 'disabled'] - ] - - disabled [ - - self disabled: true - ] -] - - diff --git a/iliad-stable/Core/HTMLElements/ILHTMLBuilderElement.st b/iliad-stable/Core/HTMLElements/ILHTMLBuilderElement.st deleted file mode 100644 index 447b4cc..0000000 --- a/iliad-stable/Core/HTMLElements/ILHTMLBuilderElement.st +++ /dev/null @@ -1,841 +0,0 @@ -"====================================================================== -| -| Iliad.ILHTMLBuilderElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILElement subclass: ILHTMLBuilderElement [ - - - - - contentType [ - - ^'text/html; charset=', self session charset - ] - - title [ - - ^self attributeAt: 'title' - ] - - title: aString [ - - ^self attributeAt: 'title' put: aString - ] - - - cssClass: aString [ - - self attributeAt: 'class' put: aString - ] - - cssClass [ - - ^self attributeAt: 'class' - ] - - class: aString [ - - self cssClass: aString - ] - - id [ - - ^self attributeAt: 'id' - ] - - id: aString [ - - self attributeAt: 'id' put: aString - ] - - lang: aString [ - - self attributeAt: 'lang' put: aString - ] - - xmlLang: aString [ - - self attributeAt: 'xml:lang' put: aString - ] - - style [ - - ^self attributeAt: 'style' - ] - - style: aString [ - - ^self attributeAt: 'style' put: aString - ] - - onBlur: aString [ - - self onEvent: 'blur' add: aString - ] - - onChange: aString [ - - self onEvent: 'change' add: aString - ] - - onClick: aString [ - - self onEvent: 'click' add: aString - ] - - onDoubleClick: aString [ - - self onEvent: 'dblclick' add: aString - ] - - onFocus: aString [ - - self onEvent: 'focus' add: aString - ] - - onKeyDown: aString [ - - self onEvent: 'keydown' add: aString - ] - - onKeyPress: aString [ - - self onEvent: 'keypress' add: aString - ] - - onKeyUp: aString [ - - self onEvent: 'keyup' add: aString - ] - - onMouseOut: aString [ - - self onEvent: 'mouseout' add: aString - ] - - onMouseOver: aString [ - - self onEvent: 'mouseover' add: aString - ] - - onSelect: aString [ - - self onEvent: 'select' add: aString - ] - - onBlurDo: aBlock [ - - self onEvent: 'blur' do: aBlock - ] - - onChangeDo: aBlock [ - - self onEvent: 'change' do: aBlock - ] - - onClickDo: aBlock [ - - self onEvent: 'click' do: aBlock - ] - - onDoubleClickDo: aBlock [ - - self onEvent: 'dblclick' do: aBlock - ] - - onFocusDo: aBlock [ - - self onEvent: 'focus' do: aBlock - ] - - onKeyDownDo: aBlock [ - - self onEvent: 'keydown' do: aBlock - ] - - onKeyPressDo: aBlock [ - - self onEvent: 'keypress' do: aBlock - ] - - onKeyUpDo: aBlock [ - - self onEvent: 'keyup' do: aBlock - ] - - onMouseOutDo: aBlock [ - - self onEvent: 'mouseout' do: aBlock - ] - - onMouseOverDo: aBlock [ - - self onEvent: 'mouseover' do: aBlock - ] - - onSelectDo: aBlock [ - - self onEvent: 'select' do: aBlock - ] - - onEvent: aString add: anotherString [ - - | oldString | - oldString := (self attributeAt: 'on', aString) ifNil: ['']. - self attributeAt: 'on', aString put: (oldString, anotherString) - ] - - onEvent: aString do: aBlock [ - - | actionUrl | - actionUrl := (self context urlBuilder urlForAction: - (self session registerActionFor: aBlock)) greaseString. - self - onEvent: aString - add: 'iliad.evaluateAction("', actionUrl, '");' - ] - - a [ - - ^self add: ILAnchorElement new - ] - - area [ - - ^self add: ILAreaElement new - ] - - bdo [ - - ^self add: ILDirectionElement new - ] - - big [ - - ^self add: (ILTextElement new - tag: 'big'; - yourself) - ] - - big: aString [ - - ^self big - contents: aString; - yourself - ] - - blockquote [ - - ^self add: (ILTextElement new - tag: 'blockquote'; - yourself) - ] - - blockquote: aString [ - - ^self blockquote - contents: aString; - yourself - ] - - b [ - - ^self add: (ILTextElement new - tag: 'b'; - yourself) - ] - - b: aString [ - - ^self b - contents: aString; - yourself - ] - - br [ - - ^self add: ILBreakElement new - ] - - button [ - - ^self add: ILButtonElement new - ] - - checkbox [ - - ^self add: ILCheckboxElement new - ] - - cite [ - - ^self add: (ILTextElement new - tag: 'cite'; - yourself) - ] - - cite: aString [ - - ^self cite - contents: aString; - yourself - ] - - code [ - - ^self add: (ILTextElement new - tag: 'code'; - yourself) - ] - - code: aString [ - - ^self code - contents: aString; - yourself - ] - - dd [ - - ^self add: (ILTextElement new - tag: 'dd'; - yourself) - ] - - dfn [ - - ^self add: (ILTextElement new - tag: 'dfn'; - yourself) - ] - - dl [ - - ^self add: (ILTextElement new - tag: 'dl'; - yourself) - ] - - dt [ - - ^self add: (ILTextElement new - tag: 'dt'; - yourself) - ] - - div [ - - ^self add: ILDivElement new - ] - - em [ - - ^self add: (ILTextElement new - tag: 'em'; - yourself) - ] - - em: aString [ - - ^self em - contents: aString; - yourself - ] - - favicon [ - - ^self link - beFavicon; - yourself - ] - - favicon: aString [ - - ^self favicon - href: aString; - yourself - ] - - fieldset [ - - ^self add: ILFieldsetElement new - ] - - file [ - - ^self input - beFile; - yourself - ] - - form [ - - ^self add: ILFormElement new - ] - - h1 [ - - ^self add: (ILHeadingElement new - level: 1; - yourself) - ] - - h1: aString [ - - ^self h1 - text: aString; - yourself - ] - - h2 [ - - ^self add: (ILHeadingElement new - level: 2; - yourself) - ] - - h2: aString [ - - ^self h2 - text: aString; - yourself - ] - - h3 [ - - ^self add: (ILHeadingElement new - level: 3; - yourself) - ] - - h3: aString [ - - ^self h3 - text: aString; - yourself - ] - - h4 [ - - ^self add: (ILHeadingElement new - level: 4; - yourself) - ] - - h4: aString [ - - ^self h4 - text: aString; - yourself - ] - - h5 [ - - ^self add: (ILHeadingElement new - level: 5; - yourself) - ] - - h5: aString [ - - ^self h5 - text: aString; - yourself - ] - - h6 [ - - ^self add: (ILHeadingElement new - level: 6; - yourself) - ] - - h6: aString [ - - ^self h6 - text: aString; - yourself - ] - - h [ - - ^self add: ILHeadingElement new - ] - - hr [ - - ^self add: ILHorizontalRuleElement new - ] - - html: aString [ - - ^self add: (ILRawHtmlElement new - contents: aString; - yourself) - ] - - if [ - - ^self add: (ILConditionalCommentElement new) - ] - - img [ - - ^self add: ILImageElement new - ] - - img: aString [ - - ^self img - src: aString; - yourself - ] - - input [ - - ^self add: ILInputElement new - ] - - i [ - - ^self add: (ILTextElement new - tag: 'i'; - yourself) - ] - - i: aString [ - - ^self i - contents: aString; - yourself - ] - - javascript [ - - ^self script - beJavascript; - yourself - ] - - label [ - - ^self add: ILLabelElement new - ] - - legend [ - - ^self add: ILLegendElement new - ] - - legend: aString [ - - ^self legend - text: aString; - yourself - ] - - link [ - - ^self add: ILLinkElement new - ] - - li [ - - ^self add: ILListItemElement new - ] - - map [ - - ^self add: ILMapElement new - ] - - meta [ - - ^self add: ILMetaElement new - ] - - nbsp [ - ^self add: (ILRawHtmlElement new - contents: ' '; - yourself) - ] - - object [ - - ^self add: ILObjectElement new - ] - - option [ - - ^self add: ILOptionElement new - ] - - optgroup [ - - ^self add: ILOptionGroupElement new - ] - - ol [ - - ^self add: (ILListElement new - beOrdered; - yourself) - ] - - p [ - - ^self add: ILParagraphElement new - ] - - param [ - - ^self add: ILParameterElement new - ] - - password [ - - ^self input - bePassword; - yourself - ] - - pre [ - - ^self add: (ILTextElement new - tag: 'pre'; - yourself) - ] - - pre: aString [ - - ^self pre - contents: aString; - yourself - ] - - quote [ - - ^self add: (ILTextElement new - tag: 'quote'; - yourself) - ] - - quote: aString [ - - ^self quote - contents: aString; - yourself - ] - - radio [ - - ^self add: ILRadioButtonElement new - ] - - reset [ - - ^self input - beReset; - yourself - ] - - script [ - - ^self add: ILScriptElement new - ] - - script: aString [ - - ^self script - contents: aString; - yourself - ] - - select [ - - ^self add: ILSelectElement new - ] - - small [ - - ^self add: (ILTextElement new - tag: 'small'; - yourself) - ] - - small: aString [ - - ^self small - contents: aString; - yourself - ] - - space [ - - ^self text: ' ' - ] - - span [ - - ^self add: ILSpanElement new - ] - - strong [ - - ^self add: (ILTextElement new - tag: 'strong'; - yourself) - ] - - strong: aString [ - - ^self strong - contents: aString; - yourself - ] - - stylesheet [ - - ^self link - beStylesheet; - yourself - ] - - submit [ - - ^self input - beSubmit; - yourself - ] - - subscript [ - - ^self add: (ILTextElement new - tag: 'subscript'; - yourself) - ] - - subscript: aString [ - - ^self subscript - contents: aString; - yourself - ] - - superscript [ - - ^self add: (ILTextElement new - tag: 'superscript'; - yourself) - ] - - superscript: aString [ - - ^self superscript - contents: aString; - yourself - ] - - table [ - - ^self add: ILTableElement new - ] - - tbody [ - - ^self add: ILTableBodyElement new - ] - - td [ - - ^self add: ILTableDataElement new - ] - - tfoot [ - - ^self add: ILTableFootElement new - ] - - thead [ - - ^self add: ILTableHeadElement new - ] - - th [ - - ^self add: ILTableHeaderElement new - ] - - tr [ - - ^self add: ILTableRowElement new - ] - - tt [ - - ^self add: (ILTextElement new - tag: 'tt'; - yourself) - ] - - textarea [ - - ^self add: ILTextAreaElement new - ] - - ul [ - - ^self - add: (ILListElement new beUnordered; - yourself) - ] - - var [ - - ^self add: (ILTextElement new - tag: 'var'; - yourself) - ] - - var: aString [ - - ^self var - contents: aString; - yourself - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILHeadElement.st b/iliad-stable/Core/HTMLElements/ILHeadElement.st deleted file mode 100644 index dd6a42d..0000000 --- a/iliad-stable/Core/HTMLElements/ILHeadElement.st +++ /dev/null @@ -1,101 +0,0 @@ -"====================================================================== -| -| Iliad.ILHeadElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILHTMLBuilderElement subclass: ILHeadElement [ - - - - - tag [ - - ^'head' - ] - - profile: aString [ - - self attributeAt: 'profile' put: aString - ] - - profiles: aCollection [ - - | profiles | - profiles := WriteStream on: String new. - aCollection do: [:each | profiles nextPutAll: each] - separatedBy: [profiles nextPutAll: ' ']. - self attributeAt: 'profile' put: profiles contents - ] - - title [ - - ^self add: ILTitleElement new - ] - - title: aString [ - - ^self add: (ILTitleElement new - text: aString; - yourself) - ] - - style [ - - ^self add: (ILTextElement new - tag: 'style'; - attributeAt: 'type' put: 'text/css'; - yourself) - ] - - style: aString [ - - ^self style - contents: aString; - yourself - ] - - onEvent: event add: aString [ - - self doesNotUnderstandAttribute: 'on' , event - ] - - beforePrintHtml [ - - (self meta) - httpEquiv: 'Content-Type'; - content: self contentType - ] -] diff --git a/iliad-stable/Core/HTMLElements/ILHeadingElement.st b/iliad-stable/Core/HTMLElements/ILHeadingElement.st deleted file mode 100644 index aafff41..0000000 --- a/iliad-stable/Core/HTMLElements/ILHeadingElement.st +++ /dev/null @@ -1,65 +0,0 @@ -"====================================================================== -| -| Iliad.ILHeadingElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILHTMLBuilderElement subclass: ILHeadingElement [ - | level | - - - - - level [ - - ^level - ] - - level: anInteger [ - - level := anInteger greaseString - ] - - tag [ - - ^'h' , self level - ] - - onEvent: event add: aString [ - - self doesNotUnderstandAttribute: 'on' , event - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILHorizontalRuleElement.st b/iliad-stable/Core/HTMLElements/ILHorizontalRuleElement.st deleted file mode 100644 index d9972fb..0000000 --- a/iliad-stable/Core/HTMLElements/ILHorizontalRuleElement.st +++ /dev/null @@ -1,54 +0,0 @@ -"====================================================================== -| -| Iliad.ILHorizontalRuleElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILClosingElement subclass: ILHorizontalRuleElement [ - - - - - tag [ - - ^'hr' - ] - - onEvent: anEvent add: aString [ - - self doesNotUnderstandAttribute: 'on' , aString - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILHtmlElement.st b/iliad-stable/Core/HTMLElements/ILHtmlElement.st deleted file mode 100644 index b34042e..0000000 --- a/iliad-stable/Core/HTMLElements/ILHtmlElement.st +++ /dev/null @@ -1,144 +0,0 @@ -"====================================================================== -| -| Iliad.ILHtmlElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILHTMLBuilderElement subclass: ILHtmlElement [ - | doctype xmlTag | - - - - - defaultXmlns [ - - ^'http://www.w3.org/1999/xhtml' - ] - - beXhtml10Strict [ - - self setXmlTag. - self doctype: '' - ] - - beXhtml10Transitional [ - - self setXmlTag. - self doctype: '' - ] - - beXhtml11 [ - - self setXmlTag. - self doctype: '' - ] - - beHtml5 [ - - self doctype: '' - ] - - doctype [ - - ^doctype - ] - - doctype: aString [ - - doctype := aString - ] - - xmlTag [ - - ^xmlTag - ] - - xmlTag: aString [ - - xmlTag := aString - ] - - setXmlTag [ - - self xmlTag: ('') - ] - - tag [ - - ^'html' - ] - - version: aNumber [ - - self attributeAt: 'version' put: aNumber greaseString - ] - - xmlns: aString [ - - self attributeAt: 'xmlns' put: aString - ] - - xmlns [ - - ^self attributeAt: 'xmlns' - ] - - onEvent: event add: aString [ - - self doesNotUnderstandAttribute: 'on' , event - ] - - beforePrintHtml [ - - self attributeAt: 'lang' ifAbsentPut: [self session language greaseString]. - self hasXmlTag ifFalse: [^self]. - self attributeAt: 'xmlns' ifAbsentPut: [self defaultXmlns]. - self attributeAt: 'xml:lang' ifAbsentPut: [self session language greaseString] - ] - - printHtmlOn: aStream [ - - self doctype ifNil: [self beXhtml10Strict]. - self hasXmlTag ifTrue: [ - aStream nextPutAll: self xmlTag]. - aStream nextPutAll: self doctype. - super printHtmlOn: aStream - ] - - hasXmlTag [ - - ^self xmlTag notNil - ] -] diff --git a/iliad-stable/Core/HTMLElements/ILImageElement.st b/iliad-stable/Core/HTMLElements/ILImageElement.st deleted file mode 100644 index bc93cc9..0000000 --- a/iliad-stable/Core/HTMLElements/ILImageElement.st +++ /dev/null @@ -1,97 +0,0 @@ -"====================================================================== -| -| Iliad.ILImageElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILClosingElement subclass: ILImageElement [ - - - - - tag [ - - ^'img' - ] - - alt: aString [ - - self attributeAt: 'alt' put: aString - ] - - height: anInteger [ - - self attributeAt: 'height' put: anInteger greaseString - ] - - ismap [ - - self attributeAt: 'ismap' put: 'ismap' - ] - - longdesc: aString [ - - self attributeAt: 'longdesc' put: aString - ] - - src: aString [ - - self attributeAt: 'src' put: aString - ] - - src: src alt: alt [ - - self - src: src; - alt: alt - ] - - usemap: aString [ - - self attributeAt: 'usemap' put: aString - ] - - width: anInteger [ - - self attributeAt: 'width' put: anInteger greaseString - ] - - beforePrintHtml [ - - self attributeAt: 'src' ifAbsent: [self attributeError: 'src not set']. - self attributeAt: 'alt' ifAbsentPut: [''] - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILInputElement.st b/iliad-stable/Core/HTMLElements/ILInputElement.st deleted file mode 100644 index 59d8e22..0000000 --- a/iliad-stable/Core/HTMLElements/ILInputElement.st +++ /dev/null @@ -1,149 +0,0 @@ -"====================================================================== -| -| Iliad.ILInputElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILFormElementElement subclass: ILInputElement [ - - - - - tag [ - - ^'input' - ] - - accept: aString [ - - self attributeAt: 'accept' put: aString - ] - - accepts: aCollection [ - - | contentTypes | - contentTypes := WriteStream on: String new. - aCollection do: [:each | contentTypes nextPutAll: each] - separatedBy: [contentTypes nextPutAll: ' ']. - self accept: contentTypes contents - ] - - alt: aString [ - - self attributeAt: 'alt' put: aString - ] - - ismap [ - - self attributeAt: 'ismap' put: 'ismap' - ] - - maxlength: anInteger [ - - self attributeAt: 'maxlength' put: anInteger greaseString - ] - - size: anInteger [ - - self attributeAt: 'size' put: anInteger greaseString - ] - - usemap: aString [ - - self attributeAt: 'usemap' put: aString - ] - - value: aString [ - - self attributeAt: 'value' put: aString - ] - - beFile [ - - self type: 'file' - ] - - beHidden [ - - self type: 'hidden' - ] - - beImage [ - - self type: 'image' - ] - - bePassword [ - - self type: 'password' - ] - - beReset [ - - self type: 'reset' - ] - - beSubmit [ - - self type: 'submit' - ] - - beText [ - - self type: 'text' - ] - - type: aString [ - - self attributeAt: 'type' put: aString - ] - - beforePrintHtml [ - - self attributeAt: 'type' ifAbsentPut: ['text']. - ] - - printHtmlOn: aStream [ - - self beforePrintHtml. - aStream - nextPut: $<; - nextPutAll: self tag. - self attributes - associationsDo: [:each | self printAttribute: each on: aStream]. - aStream nextPutAll: '/>' - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILLabelElement.st b/iliad-stable/Core/HTMLElements/ILLabelElement.st deleted file mode 100644 index 63e3286..0000000 --- a/iliad-stable/Core/HTMLElements/ILLabelElement.st +++ /dev/null @@ -1,59 +0,0 @@ -"====================================================================== -| -| Iliad.ILLabelElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILHTMLBuilderElement subclass: ILLabelElement [ - - - - - tag [ - - ^'label' - ] - - accesskey: aCharacter [ - - self attributeAt: 'accesskey' put: aCharacter greaseString - ] - - for: aString [ - - self attributeAt: 'for' put: aString - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILLegendElement.st b/iliad-stable/Core/HTMLElements/ILLegendElement.st deleted file mode 100644 index 0440671..0000000 --- a/iliad-stable/Core/HTMLElements/ILLegendElement.st +++ /dev/null @@ -1,54 +0,0 @@ -"====================================================================== -| -| Iliad.ILLegendElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILHTMLBuilderElement subclass: ILLegendElement [ - - - - - tag [ - - ^'legend' - ] - - accesskey: aCharacter [ - - self attributeAt: 'accesskey' put: aCharacter greaseString - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILLinkElement.st b/iliad-stable/Core/HTMLElements/ILLinkElement.st deleted file mode 100644 index 8929848..0000000 --- a/iliad-stable/Core/HTMLElements/ILLinkElement.st +++ /dev/null @@ -1,112 +0,0 @@ -"====================================================================== -| -| Iliad.ILLinkElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILLinkableElement subclass: ILLinkElement [ - - - - - tag [ - - ^'link' - ] - - allMedia [ - - self media: 'all' - ] - - auralMedia [ - - self media: 'aural' - ] - - brailleMedia [ - - self media: 'braille' - ] - - handheldMedia [ - - self media: 'handheld' - ] - - media: aString [ - - self attributeAt: 'media' put: aString - ] - - printMedia [ - - self media: 'print' - ] - - projectionMedia [ - - self media: 'projection' - ] - - screenMedia [ - - self media: 'screen' - ] - - ttyMedia [ - - self media: 'tty' - ] - - tvMedia [ - - self media: 'tv' - ] - - type: aString [ - - self attributeAt: 'type' put: aString - ] - - printHtmlOn: aStream [ - - aStream nextPutAll: '<' , self tag. - self attributes - associationsDo: [:each | self printAttribute: each on: aStream]. - aStream nextPutAll: '/>' - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILLinkableElement.st b/iliad-stable/Core/HTMLElements/ILLinkableElement.st deleted file mode 100644 index 27f8209..0000000 --- a/iliad-stable/Core/HTMLElements/ILLinkableElement.st +++ /dev/null @@ -1,275 +0,0 @@ -"====================================================================== -| -| Iliad.ILLinkableElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILHTMLBuilderElement subclass: ILLinkableElement [ - - - - - accesskey: aCharacter [ - - self attributeAt: 'accesskey' put: aCharacter greaseString - ] - - charset: aString [ - - self attributeAt: 'charset' put: aString - ] - - contentType: aString [ - - self type: aString - ] - - href: aString [ - - self attributeAt: 'href' put: aString - ] - - hreflang: aString [ - - self attributeAt: 'hreflang' put: aString - ] - - target: aString [ - - self attributeAt: 'target' put: aString - ] - - linkToLocal: aString [ - - self linkToApplication: self application class controller: aString - ] - - linkToApplication: anApplicationClass [ - - self linkToApplication: anApplicationClass controller: '' - ] - - linkToApplication: anApplicationClass controller: aString [ - - self href: (self context urlBuilder urlFor: anApplicationClass path, '/', aString) - ] - - type: aString [ - - self attributeAt: 'type' put: aString - ] - - beAlternate [ - - self rel: 'Alternate' - ] - - beAppendix [ - - self rel: 'Appendix' - ] - - beBookmark [ - - self rel: 'Bookmark' - ] - - beChapter [ - - self rel: 'Chapter' - ] - - beContents [ - - self rel: 'Contents' - ] - - beCopyright [ - - self rel: 'Copyright' - ] - - beFavicon [ - - self rel: 'shortcut icon' - ] - - beGlossary [ - - self rel: 'Glossary' - ] - - beHelp [ - - self rel: 'Help' - ] - - beIndex [ - - self rel: 'Index' - ] - - beNext [ - - self rel: 'Next' - ] - - bePrev [ - - self rel: 'Prev' - ] - - bePrevious [ - - self rel: 'Prev' - ] - - beRss [ - - self rel: 'alternate'. - self type: 'application/rss+xml' - ] - - beSection [ - - self rel: 'Section' - ] - - beStart [ - - self rel: 'Start' - ] - - beStylesheet [ - - self rel: 'Stylesheet'. - self type: 'text/css' - ] - - beSubsection [ - - self rel: 'Subsection' - ] - - rel: aString [ - - self attributeAt: 'rel' put: aString - ] - fromAlternate [ - - self rev: 'Alternate' - ] - - fromAppendix [ - - self rev: 'Appendix' - ] - - fromBookmark [ - - self rev: 'Bookmark' - ] - - fromChapter [ - - self rev: 'Chapter' - ] - - fromContents [ - - self rev: 'Contents' - ] - - fromCopyright [ - - self rev: 'Copyright' - ] - - fromGlossary [ - - self rev: 'Glossary' - ] - - fromHelp [ - - self rev: 'Help' - ] - - fromIndex [ - - self rev: 'Index' - ] - - fromNext [ - - self rev: 'Next' - ] - - fromPrev [ - - self rev: 'Prev' - ] - - fromPrevious [ - - self rev: 'Prev' - ] - - fromSection [ - - self rev: 'Section' - ] - - fromStart [ - - self rev: 'Start' - ] - - fromStylesheet [ - - self rev: 'Stylesheet' - ] - - fromSubsection [ - - self rev: 'Subsection' - ] - - rev: aString [ - - self attributeAt: 'rev' put: aString - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILListElement.st b/iliad-stable/Core/HTMLElements/ILListElement.st deleted file mode 100644 index 4b290a6..0000000 --- a/iliad-stable/Core/HTMLElements/ILListElement.st +++ /dev/null @@ -1,65 +0,0 @@ -"====================================================================== -| -| Iliad.ILListElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILHTMLBuilderElement subclass: ILListElement [ - | tag | - - - - - beOrdered [ - - self tag: 'ol' - ] - - beUnordered [ - - self tag: 'ul' - ] - - tag [ - - ^tag - ] - - tag: aString [ - - tag := aString - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILListItemElement.st b/iliad-stable/Core/HTMLElements/ILListItemElement.st deleted file mode 100644 index d631d4d..0000000 --- a/iliad-stable/Core/HTMLElements/ILListItemElement.st +++ /dev/null @@ -1,49 +0,0 @@ -"====================================================================== -| -| Iliad.ILListItemElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILHTMLBuilderElement subclass: ILListItemElement [ - - - - - tag [ - - ^'li' - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILMapElement.st b/iliad-stable/Core/HTMLElements/ILMapElement.st deleted file mode 100644 index cea8d7d..0000000 --- a/iliad-stable/Core/HTMLElements/ILMapElement.st +++ /dev/null @@ -1,54 +0,0 @@ -"====================================================================== -| -| Iliad.ILMapElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILHTMLBuilderElement subclass: ILMapElement [ - - - - - tag [ - - ^'map' - ] - - classes: aCollection [ - - ILAttributeError signal: 'map tag can have one class only' - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILMetaElement.st b/iliad-stable/Core/HTMLElements/ILMetaElement.st deleted file mode 100644 index 225a2da..0000000 --- a/iliad-stable/Core/HTMLElements/ILMetaElement.st +++ /dev/null @@ -1,115 +0,0 @@ -"====================================================================== -| -| Iliad.ILMetaElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILClosingElement subclass: ILMetaElement [ - - - - - tag [ - - ^'meta' - ] - - class: aString [ - - self doesNotUnderstandAttribute: 'class' - ] - - classes: aCollection [ - - self doesNotUnderstandAttribute: 'class' - ] - - content: aString [ - - self attributeAt: 'content' put: aString - ] - - contentType [ - - self httpEquiv: 'content-type' - ] - - expires [ - - self httpEquiv: 'expires' - ] - - httpEquiv: aString [ - - self attributeAt: 'http-equiv' put: aString - ] - - name: aString [ - - self attributeAt: 'name' put: aString - ] - - refresh [ - - self httpEquiv: 'refresh' - ] - - scheme: aString [ - - self attributeAt: 'scheme' put: aString - ] - - setCookie [ - - self httpEquiv: 'set-cookie' - ] - - title: aString [ - - self doesNotUnderstandAttribute: 'title' - ] - - onEvent: event add: aString [ - - self doesNotUnderstandAttribute: 'on' , event - ] - - beforePrintHtml [ - - self attributeAt: 'content' - ifAbsent: [self attributeError: 'content not set'] - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILObjectElement.st b/iliad-stable/Core/HTMLElements/ILObjectElement.st deleted file mode 100644 index 29e7c40..0000000 --- a/iliad-stable/Core/HTMLElements/ILObjectElement.st +++ /dev/null @@ -1,128 +0,0 @@ -"====================================================================== -| -| Iliad.ILObjectElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILHTMLBuilderElement subclass: ILObjectElement [ - - - - - tag [ - - ^'object' - ] - - archive: aString [ - - self attributeAt: 'archive' put: aString - ] - - archives: aCollection [ - - | archives | - archives := WriteStream on: String new. - aCollection do: [:each | archives nextPutAll: each] - separatedBy: [archives nextPutAll: ' ']. - self attributeAt: 'archive' put: archives contents - ] - - classid: aString [ - - self attributeAt: 'classid' put: aString - ] - - codebase: aString [ - - self attributeAt: 'codebase' put: aString - ] - - codetype: aString [ - - self attributeAt: 'codetype' put: aString - ] - - data: aString [ - - self attributeAt: 'data' put: aString - ] - - declare [ - - self attributeAt: 'declare' put: 'declare' - ] - - declareOnly [ - - self declare - ] - - height: anInteger [ - - self attributeAt: 'height' put: anInteger greaseString - ] - - name: aString [ - - self attributeAt: 'name' put: aString - ] - - standby: aString [ - - self attributeAt: 'standby' put: aString - ] - - tabindex: anInteger [ - - self attributeAt: 'tabindex' put: anInteger greaseString - ] - - type: aString [ - - self attributeAt: 'type' put: aString - ] - - usemap: aString [ - - self attributeAt: 'usemap' put: aString - ] - - width: anInteger [ - - self attributeAt: 'width' put: anInteger greaseString - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILOptionElement.st b/iliad-stable/Core/HTMLElements/ILOptionElement.st deleted file mode 100644 index 3ed4e84..0000000 --- a/iliad-stable/Core/HTMLElements/ILOptionElement.st +++ /dev/null @@ -1,91 +0,0 @@ -"====================================================================== -| -| Iliad.ILOptionElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILHTMLBuilderElement subclass: ILOptionElement [ - - - - - tag [ - - ^'option' - ] - - action: aBlock [ - - | action | - action := self session registerActionFor: aBlock. - self value: action key - ] - - selected: aBoolean [ - - aBoolean ifTrue: [self selected] - ] - - label: aString [ - - self attributeAt: 'label' put: aString - ] - - selected [ - - self attributeAt: 'selected' put: 'selected' - ] - - selected: aBoolean [ - - aBoolean ifTrue: [self selected] - ] - - disabled [ - - self attributeAt: 'disabled' put: 'disabled' - ] - - disabled: aBoolean [ - - aBoolean ifTrue: [self disabled] - ] - - value: aString [ - - self attributeAt: 'value' put: aString - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILOptionGroupElement.st b/iliad-stable/Core/HTMLElements/ILOptionGroupElement.st deleted file mode 100644 index 63cbe2f..0000000 --- a/iliad-stable/Core/HTMLElements/ILOptionGroupElement.st +++ /dev/null @@ -1,65 +0,0 @@ -"====================================================================== -| -| Iliad.ILOptionGroupElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILHTMLBuilderElement subclass: ILOptionGroupElement [ - - - - - tag [ - - ^'optgroup' - ] - - label: aString [ - - self attributeAt: 'label' put: aString - ] - - disabled [ - - self attributeAt: 'disabled' put: 'disabled' - ] - - disabled: aBoolean [ - - aBoolean ifTrue: [self disabled] - ] -] - - diff --git a/iliad-stable/Core/HTMLElements/ILParagraphElement.st b/iliad-stable/Core/HTMLElements/ILParagraphElement.st deleted file mode 100644 index 0e3bd3a..0000000 --- a/iliad-stable/Core/HTMLElements/ILParagraphElement.st +++ /dev/null @@ -1,49 +0,0 @@ -"====================================================================== -| -| Iliad.ILParagraphElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILHTMLBuilderElement subclass: ILParagraphElement [ - - - - - tag [ - - ^'p' - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILParameterElement.st b/iliad-stable/Core/HTMLElements/ILParameterElement.st deleted file mode 100644 index 00503bd..0000000 --- a/iliad-stable/Core/HTMLElements/ILParameterElement.st +++ /dev/null @@ -1,96 +0,0 @@ -"====================================================================== -| -| Iliad.ILParameterElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILClosingElement subclass: ILParameterElement [ - - - - - tag [ - - ^'param' - ] - - - beData [ - - self valuetype: 'data' - ] - - beObject [ - - self valuetype: 'object' - ] - - beReference [ - - self valuetype: 'ref' - ] - - name: aString [ - - self attributeAt: 'name' put: aString - ] - - type: aString [ - - self attributeAt: 'type' put: aString - ] - - value: aString [ - - self attributeAt: 'value' put: aString - ] - - valuetype: aString [ - - self attributeAt: 'valuetype' put: aString - ] - - add: anElement [ - - ILElementError signal: 'Can''t add an element to a' , self class name - ] - - beforePrintHtml [ - - self attributeAt: 'name' - ifAbsent: [self attributeError: 'name can''t be null'] - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILRadioButtonElement.st b/iliad-stable/Core/HTMLElements/ILRadioButtonElement.st deleted file mode 100644 index daa9a2f..0000000 --- a/iliad-stable/Core/HTMLElements/ILRadioButtonElement.st +++ /dev/null @@ -1,76 +0,0 @@ -"====================================================================== -| -| Iliad.ILRadioButtonElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILFormElementElement subclass: ILRadioButtonElement [ - - - - - tag [ - - ^'input' - ] - - action: aBlock [ - - | action | - action := self session registerActionFor: aBlock. - self value: action key - ] - - beSelected [ - - self selected: true - ] - - selected: aBoolean [ - - aBoolean ifTrue: [self attributeAt: 'checked' put: 'checked'] - ] - - value: aString [ - - self attributeAt: 'value' put: aString - ] - - beforePrintHtml [ - - self attributeAt: 'type' put: 'radio' - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILRawHtmlElement.st b/iliad-stable/Core/HTMLElements/ILRawHtmlElement.st deleted file mode 100644 index 653e216..0000000 --- a/iliad-stable/Core/HTMLElements/ILRawHtmlElement.st +++ /dev/null @@ -1,60 +0,0 @@ -"====================================================================== -| -| Iliad.ILRawHtmlElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILElement subclass: ILRawHtmlElement [ - | contents | - - - - - contents [ - - ^contents ifNil: [''] - ] - - contents: aString [ - - contents := aString - ] - - printHtmlOn: aStream [ - - aStream nextPutAll: self contents - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILRubyTextElement.st b/iliad-stable/Core/HTMLElements/ILRubyTextElement.st deleted file mode 100644 index b596c8e..0000000 --- a/iliad-stable/Core/HTMLElements/ILRubyTextElement.st +++ /dev/null @@ -1,54 +0,0 @@ -"====================================================================== -| -| Iliad.ILRubyTextElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILHTMLBuilderElement subclass: ILRubyTextElement [ - - - - - tag [ - - ^'rt' - ] - - rbspan: anInteger [ - - self attributeAt: 'rbspan' put: anInteger greaseString - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILScriptElement.st b/iliad-stable/Core/HTMLElements/ILScriptElement.st deleted file mode 100644 index 457e0e9..0000000 --- a/iliad-stable/Core/HTMLElements/ILScriptElement.st +++ /dev/null @@ -1,103 +0,0 @@ -"====================================================================== -| -| Iliad.ILScriptElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILHTMLBuilderElement subclass: ILScriptElement [ - | contents | - - - - - contents [ - - ^contents ifNil: [''] - ] - - contents: aString [ - - contents := aString - ] - - tag [ - - ^'script' - ] - - beJavascript [ - - self type: 'text/javascript' - ] - - charset: aString [ - - self attributeAt: 'charset' put: aString - ] - - defer [ - - self attributeAt: 'defer' put: 'defer' - ] - - language: aString [ - - self attributeAt: 'language' put: aString - ] - - src: aString [ - - self attributeAt: 'src' put: aString - ] - - type: aString [ - - self attributeAt: 'type' put: aString - ] - - beforePrintHtml [ - - self attributeAt: 'type' ifAbsent: [self beJavascript] - ] - - printHtmlOn: aStream [ - "do not encode contents!!" - - self printOpenTagOn: aStream. - aStream nextPutAll: self contents. - self printCloseTagOn: aStream - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILSelectElement.st b/iliad-stable/Core/HTMLElements/ILSelectElement.st deleted file mode 100644 index 52e07bc..0000000 --- a/iliad-stable/Core/HTMLElements/ILSelectElement.st +++ /dev/null @@ -1,72 +0,0 @@ -"====================================================================== -| -| Iliad.ILSelectElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILFormElementElement subclass: ILSelectElement [ - - - - - initialize [ - - super initialize. - super action: [:val | - val do: [:each | - self session evaluateActionKey: each]] - ] - - tag [ - - ^'select' - ] - - action: aBlock [ - - self shouldNotImplement - ] - - beMultiple [ - - self attributeAt: 'multiple' put: 'multiple' - ] - - size: anInteger [ - - self attributeAt: 'size' put: anInteger greaseString - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILSpanElement.st b/iliad-stable/Core/HTMLElements/ILSpanElement.st deleted file mode 100644 index fd15668..0000000 --- a/iliad-stable/Core/HTMLElements/ILSpanElement.st +++ /dev/null @@ -1,49 +0,0 @@ -"====================================================================== -| -| Iliad.ILSpanElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILHTMLBuilderElement subclass: ILSpanElement [ - - - - - tag [ - - ^'span' - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILTableBodyElement.st b/iliad-stable/Core/HTMLElements/ILTableBodyElement.st deleted file mode 100644 index f30c686..0000000 --- a/iliad-stable/Core/HTMLElements/ILTableBodyElement.st +++ /dev/null @@ -1,49 +0,0 @@ -"====================================================================== -| -| Iliad.ILTableBodyElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILTableElementElement subclass: ILTableBodyElement [ - - - - - tag [ - - ^'tbody' - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILTableCellElement.st b/iliad-stable/Core/HTMLElements/ILTableCellElement.st deleted file mode 100644 index 89a15af..0000000 --- a/iliad-stable/Core/HTMLElements/ILTableCellElement.st +++ /dev/null @@ -1,98 +0,0 @@ -"====================================================================== -| -| Iliad.ILTableCellElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILTableElementElement subclass: ILTableCellElement [ - - - - - abbr: aString [ - - self attributeAt: 'abbr' put: aString - ] - - axis: aString [ - - self attributeAt: 'axis' put: aString - ] - - colgroupScope [ - - self scope: 'colgroup' - ] - - colScope [ - - self scope: 'col' - ] - - colspan: anInteger [ - - self attributeAt: 'colspan' put: anInteger greaseString - ] - - headers: aCollection [ - - | headers | - headers := WriteStream on: String new. - aCollection do: [:each | headers nextPutAll: each] - separatedBy: [headers nextPutAll: ',']. - self attributeAt: 'headers' put: headers contents - ] - - rowgroupScope [ - - self scope: 'rowgroup' - ] - - rowScope [ - - self scope: 'row' - ] - - rowspan: anInteger [ - - self attributeAt: 'rowspan' put: anInteger greaseString - ] - - scope: aString [ - - self attributeAt: 'scope' put: aString - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILTableDataElement.st b/iliad-stable/Core/HTMLElements/ILTableDataElement.st deleted file mode 100644 index 8b358aa..0000000 --- a/iliad-stable/Core/HTMLElements/ILTableDataElement.st +++ /dev/null @@ -1,49 +0,0 @@ -"====================================================================== -| -| Iliad.ILTableDataElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILTableCellElement subclass: ILTableDataElement [ - - - - - tag [ - - ^'td' - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILTableElement.st b/iliad-stable/Core/HTMLElements/ILTableElement.st deleted file mode 100644 index b378a13..0000000 --- a/iliad-stable/Core/HTMLElements/ILTableElement.st +++ /dev/null @@ -1,154 +0,0 @@ -"====================================================================== -| -| Iliad.ILTableElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILHTMLBuilderElement subclass: ILTableElement [ - - - - - tag [ - - ^'table' - ] - - aboveFrame [ - - self frame: 'above' - ] - - allRules [ - - self rules: 'all' - ] - - belowFrame [ - - self frame: 'below' - ] - - border: anInteger [ - - self attributeAt: 'border' put: anInteger greaseString - ] - - borderFrame [ - - self frame: 'border' - ] - - boxFrame [ - - self frame: 'box' - ] - - cellpadding: anInteger [ - - self attributeAt: 'cellpadding' put: anInteger greaseString - ] - - cellspacing: anInteger [ - - self attributeAt: 'cellspacing' put: anInteger greaseString - ] - - colsRules [ - - self rules: 'cols' - ] - - frame: aString [ - - self attributeAt: 'frame' put: aString - ] - - groupRules [ - - self rules: 'groups' - ] - - hsidesFrame [ - - self frame: 'hsides' - ] - - lhsFrame [ - - self frame: 'lhs' - ] - - noRules [ - - self rules: 'none' - ] - - rhsFrame [ - - self frame: 'rhs' - ] - - rowsRules [ - - self rules: 'rows' - ] - - rules: aString [ - - self attributeAt: 'rules' put: aString - ] - - summary: aString [ - - self attributeAt: 'summary' put: aString - ] - - vsidesFrame [ - - self frame: 'vsides' - ] - - voidFrame [ - - self frame: 'void' - ] - - width: anInteger [ - - self attributeAt: 'width' put: anInteger greaseString - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILTableElementElement.st b/iliad-stable/Core/HTMLElements/ILTableElementElement.st deleted file mode 100644 index df08ffa..0000000 --- a/iliad-stable/Core/HTMLElements/ILTableElementElement.st +++ /dev/null @@ -1,115 +0,0 @@ -"====================================================================== -| -| Iliad.ILTableElementElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILHTMLBuilderElement subclass: ILTableElementElement [ - - - - - align: aString [ - - self attributeAt: 'align' put: aString - ] - - baselineValign [ - - self valign: 'baseline' - ] - - bottomValign [ - - self valign: 'bottom' - ] - - centerAlign [ - - self align: 'center' - ] - - character: aCharacter [ - - | alignment | - alignment := self attributeAt: 'align' ifAbsent: ['left']. - alignment = 'char' - ifFalse: [self attributeError: 'Alignment must be "char"']. - self attributeAt: 'char' put: aCharacter greaseString - ] - - characterAlign [ - - self align: 'char' - ] - - charoff: anInteger [ - - self attributeAt: 'char' - ifAbsent: [self attributeError: 'Must specify alignment character']. - self attributeAt: 'charoff' put: anInteger greaseString - ] - - justifyAlign [ - - self align: 'justify' - ] - - leftAlign [ - - self align: 'left' - ] - - middleValign [ - - self valign: 'middle' - ] - - rightAlign [ - - self align: 'right' - ] - - topValign [ - - self valign: 'top' - ] - - valign: aString [ - - self attributeAt: 'valign' put: aString - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILTableFootElement.st b/iliad-stable/Core/HTMLElements/ILTableFootElement.st deleted file mode 100644 index fe9e137..0000000 --- a/iliad-stable/Core/HTMLElements/ILTableFootElement.st +++ /dev/null @@ -1,49 +0,0 @@ -"====================================================================== -| -| Iliad.ILTableFootElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILTableElementElement subclass: ILTableFootElement [ - - - - - tag [ - - ^'tfoot' - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILTableHeadElement.st b/iliad-stable/Core/HTMLElements/ILTableHeadElement.st deleted file mode 100644 index 64195e4..0000000 --- a/iliad-stable/Core/HTMLElements/ILTableHeadElement.st +++ /dev/null @@ -1,49 +0,0 @@ -"====================================================================== -| -| Iliad.ILTableHeadElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILTableElementElement subclass: ILTableHeadElement [ - - - - - tag [ - - ^'thead' - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILTableHeaderElement.st b/iliad-stable/Core/HTMLElements/ILTableHeaderElement.st deleted file mode 100644 index af94896..0000000 --- a/iliad-stable/Core/HTMLElements/ILTableHeaderElement.st +++ /dev/null @@ -1,49 +0,0 @@ -"====================================================================== -| -| Iliad.ILTableHeaderElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILTableCellElement subclass: ILTableHeaderElement [ - - - - - tag [ - - ^'th' - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILTableRowElement.st b/iliad-stable/Core/HTMLElements/ILTableRowElement.st deleted file mode 100644 index 1800cf6..0000000 --- a/iliad-stable/Core/HTMLElements/ILTableRowElement.st +++ /dev/null @@ -1,49 +0,0 @@ -"====================================================================== -| -| Iliad.ILTableRowElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILTableCellElement subclass: ILTableRowElement [ - - - - - tag [ - - ^'tr' - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILTextAreaElement.st b/iliad-stable/Core/HTMLElements/ILTextAreaElement.st deleted file mode 100644 index aaac51d..0000000 --- a/iliad-stable/Core/HTMLElements/ILTextAreaElement.st +++ /dev/null @@ -1,64 +0,0 @@ -"====================================================================== -| -| Iliad.ILTextAreaElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILFormElementElement subclass: ILTextAreaElement [ - - - - - tag [ - - ^'textarea' - ] - - cols: anInteger [ - - self attributeAt: 'cols' put: anInteger greaseString - ] - - rows: anInteger [ - - self attributeAt: 'rows' put: anInteger greaseString - ] - - tabindex: anInteger [ - - self attributeAt: 'tabindex' put: anInteger greaseString - ] -] - diff --git a/iliad-stable/Core/HTMLElements/ILTitleElement.st b/iliad-stable/Core/HTMLElements/ILTitleElement.st deleted file mode 100644 index 3052ed5..0000000 --- a/iliad-stable/Core/HTMLElements/ILTitleElement.st +++ /dev/null @@ -1,54 +0,0 @@ -"====================================================================== -| -| Iliad.ILTitleElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILHTMLBuilderElement subclass: ILTitleElement [ - - - - - tag [ - - ^'title' - ] - - onEvent: anEvent add: aString [ - - self doesNotUnderstandAttribute: 'on' , anEvent - ] -] - diff --git a/iliad-stable/Core/Public/images/ajax_loader.gif b/iliad-stable/Core/Public/images/ajax_loader.gif deleted file mode 100644 index 1a317f8..0000000 Binary files a/iliad-stable/Core/Public/images/ajax_loader.gif and /dev/null differ diff --git a/iliad-stable/Core/Public/images/iliad.png b/iliad-stable/Core/Public/images/iliad.png deleted file mode 100644 index 5c0cce9..0000000 Binary files a/iliad-stable/Core/Public/images/iliad.png and /dev/null differ diff --git a/iliad-stable/Core/Public/images/iliad_big.png b/iliad-stable/Core/Public/images/iliad_big.png deleted file mode 100644 index 80e7bdd..0000000 Binary files a/iliad-stable/Core/Public/images/iliad_big.png and /dev/null differ diff --git a/iliad-stable/Core/Public/images/iliad_bleached.png b/iliad-stable/Core/Public/images/iliad_bleached.png deleted file mode 100644 index bce5697..0000000 Binary files a/iliad-stable/Core/Public/images/iliad_bleached.png and /dev/null differ diff --git a/iliad-stable/Core/Public/images/iliad_huge.png b/iliad-stable/Core/Public/images/iliad_huge.png deleted file mode 100644 index 54eb8db..0000000 Binary files a/iliad-stable/Core/Public/images/iliad_huge.png and /dev/null differ diff --git a/iliad-stable/Core/Public/images/iliad_small.png b/iliad-stable/Core/Public/images/iliad_small.png deleted file mode 100644 index eaac560..0000000 Binary files a/iliad-stable/Core/Public/images/iliad_small.png and /dev/null differ diff --git a/iliad-stable/Core/Public/images/iliad_tiny.png b/iliad-stable/Core/Public/images/iliad_tiny.png deleted file mode 100644 index ee75c95..0000000 Binary files a/iliad-stable/Core/Public/images/iliad_tiny.png and /dev/null differ diff --git a/iliad-stable/Core/Public/javascripts/iliad.js b/iliad-stable/Core/Public/javascripts/iliad.js deleted file mode 100644 index 6616da1..0000000 --- a/iliad-stable/Core/Public/javascripts/iliad.js +++ /dev/null @@ -1,395 +0,0 @@ -/* ==================================================================== -| -| iliad.js -| - ====================================================================== - - ====================================================================== -| -| Copyright (c) 2008-2009 -| Nicolas Petton , -| Sébastien Audier -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ==================================================================== */ - - -var iliad = (function() { - - - /* --- - * Variables - * -------------------------------------------------------------- */ - - var hash = ""; - var actionsLocked = false; - var ajax_enabled = true; - var ie67 = false; - var ajaxLoader = false; - - - /* --- - * Initialization - * -------------------------------------------------------------- */ - - function initialize() { - ie67 = jQuery.browser.msie && parseInt(jQuery.browser.version) < 8; - if(ie67) { - var iDoc = jQuery("").prependTo("body")[0]; - var iframe = iDoc.contentWindow.document || iDoc.document; - if(window.location.hash) { - hash = window.location.hash.substr(1); - iframe.location.hash = hash; - evaluateAction(window.location.pathname + '?_hash=' + hash); - } - iframe.location.title = window.title; - } - checkHashChange(); - enableAjaxActions() - } - - function enableAjaxActions() { - jQuery('body').click(function(event) { - if (event.metaKey) - return; - var anchor = jQuery(event.target).closest("a"); - if(anchor.length == 1) { - if(hasActionUrl(anchor)) { - evaluateAnchorAction(anchor, event); - } - } - var button = jQuery(event.target).closest("button"); - if(button.length == 1) { - addHiddenInput(button); - evaluateFormElementAction(button, event); - removeHiddenInput(button); - } - }) - } - - - /* --- - * Action evaluation - * -------------------------------------------------------------- */ - - function evaluateAnchorAction(anchor, event) { - if(hasActionUrl(anchor) && ajax_enabled) { - var actionUrl = jQuery(anchor).attr('href'); - evaluateAction(actionUrl); - if(hasHashUrl(anchor)) { - setHash(hashUrl(anchor)); - }; - if(event) event.preventDefault(); - } - } - - function evaluateFormElementAction(formElement, event) { - var form = jQuery(formElement).closest("form"); - if(ajax_enabled) { - if(isMultipart(form)) { - evaluateMultipartFormAction(form); - } else { - evaluateFormAction(form); - if(event) event.preventDefault(); - } - } - } - - function addHiddenInput(button) { - var name = jQuery(button).attr("name"); - if(name) { - var hidden = ""; - var form = jQuery(button).closest("form"); - jQuery(form).append(hidden); - } - } - - function removeHiddenInput(button) { - var name = jQuery(button).attr("name"); - if(name) { - jQuery(button).closest("form") - .find("input:hidden[name="+ name + "]") - .replaceWith(""); - } - } - - function evaluateFormAction(form) { - var actionUrl = getFormActionUrl(form); - var data = jQuery(form).serialize(); - evaluateAction(actionUrl, "post", data); - } - - function evaluateMultipartFormAction(form) { - if(!actionsLocked) { - var hidden = ""; - var upload_target = jQuery('#_upload_target'); - if(upload_target.size() == 0) { - upload_target = jQuery( - ""); - upload_target.appendTo('body'); - } - upload_target.one('load', function(e) { - evaluateAction(jQuery(form).children("input[name=_callback]").val()); - }); - jQuery(form).append(hidden); - jQuery(form).attr('target', '_upload_target'); - startUpload(form); - } - else {return false} - } - - - function evaluateAction(actionUrl, method, data, lock) { - if(!actionsLocked) { - if(!method) method = 'get'; - if(lock == null) lock = true; - if(lock) lockActions(); - jQuery.ajax({ - url: actionUrl, - type: method, - processUpdates: true, - dataType: 'json', - data: data, - beforeSend: function(xhr) { - if(ajaxLoader) insertAjaxLoader();}, - success: function(json) { - processUpdates(json); - if(ajaxLoader) removeAjaxLoader(); - unlockActions(); - }, - error: function(err) { - showError(err, actionUrl); - unlockActions(); - } - }); - } - } - - function lockActions() { - actionsLocked = true; - } - - function unlockActions() { - actionsLocked = false; - } - - function disableAjax() { - ajax_enabled = false - } - - function enableAjax() { - ajax_enabled = true - } - - function hasActionUrl(anchor) { - if(anchor && jQuery(anchor).attr('href')) { - return (/_action?=(.*)$/).test(jQuery(anchor).attr('href')); - } - } - - function hasHashUrl(anchor) { - if(anchor && jQuery(anchor).attr('href')) { - return (/_hash?=(.*)$/).test(jQuery(anchor).attr('href')); - } - } - - function hashUrl(anchor) { - return /_hash=([^\#|\&]+)/.exec(anchor.attr('href'))[1] - } - - function isMultipart(form) { - return jQuery(form).attr('enctype') == "multipart/form-data"; - } - - function getFormActionUrl(form) { - return jQuery(form).attr('action'); - } - - - /* --- - * Enable bookmarking for ajax actions - * and fix the back button - * -------------------------------------------------------------- */ - - function checkHashChange() { - var newHash = getHash(); - if(hash != newHash) { - hash = newHash; - if(ie67) window.location.hash = hash; - evaluateAction(window.location.pathname + '?_hash=' + hash); - } - } - - function setHash(hashString) { - hash = hashString; - window.location.hash = hash; - //IE is different, as usual.... - if(ie67) fixHistoryForIE(); - } - - function getHash() { - if(ie67) { - var newHash = getIframe().location.hash; - return newHash.substr(1); - } - return window.location.hash.substr(1); - } - - function getIframe() { - return jQuery('#_iliad_ie_history_iframe')[0].contentWindow.document; - } - - //Special hack for IE < 8. - //Else IE won't add an entry to the history - function fixHistoryForIE() { - //Add history entry - getIframe().open(); - getIframe().close(); - getIframe().location.hash = hash; - } - - - /* --- - * Page updates - * -------------------------------------------------------------- */ - - function processUpdates(json) { - var script_extractor= //ig; - var scripts = []; - - /* handle redirect if any */ - if(json.redirect) { - return (window.location.href = json.redirect); - } - - /* update head */ - for (var i in json.head) { - jQuery('head').append(json.head[i]); - } - - /* update application */ - if(json.application) { - jQuery('body').html(json.application) - } - - /* update dirty widgets */ - var dirtyWidgets = json.widgets; - for(var i in dirtyWidgets) { - var script = dirtyWidgets[i].match(script_extractor); - if(script) { - for(var j = 0; j < script.length; j++) { - scripts.push(script[j]); - } - } - updateWidget(i, dirtyWidgets[i].replace(script_extractor, '')); - } - - /* evaluate scripts */ - //var scripts = json.scripts; - for(var i in scripts) { - evalScript(scripts[i]); - } - } - - function updateWidget(id, contents) { - jQuery("."+id).replaceWith(contents); - } - - function evalScript(script) { - eval(jQuery(script).html()); - } - - - /* --- - * Various - * -------------------------------------------------------------- */ - - function showAjaxLoader(bool) { - ajaxLoader = bool - } - - function insertAjaxLoader() { - jQuery('body').append( - "
" + - "
"); - } - - function showError(error, actionUrl){ - //jQuery("body").html("

Error 500: Internal server error

"); - } - - function removeAjaxLoader() { - jQuery(".ajax_loader, .ajax_upload").replaceWith(""); - } - - function sizeOf(obj) { - var size = 0, key; - for (key in obj) { - if (obj[key] !== Object.prototype[key]) size++; - //if (obj.hasOwnProperty(key)) size++; - } - return size; - } - - function startUpload(form){ - var fileInputs = jQuery(form).find('input:file'); - jQuery.each(fileInputs, function(){ - if(jQuery(this).val()) { - jQuery(this).after( - '
loading...
' + - '
'); - } - }) - } - - - /* --- - * Public API - * -------------------------------------------------------------- */ - - return { - evaluateAnchorAction: evaluateAnchorAction, - evaluateFormAction: evaluateFormAction, - evaluateMultipartFormAction: evaluateMultipartFormAction, - evaluateFormElementAction: evaluateFormElementAction, - evaluateAction: evaluateAction, - checkHashChange: checkHashChange, - showAjaxLoader: showAjaxLoader, - disableAjax: disableAjax, - enableAjax: enableAjax, - initialize: initialize - }; -})(); - - -jQuery(document).ready(function() { - iliad.initialize(); - setInterval(iliad.checkHashChange, 200); -}); - diff --git a/iliad-stable/Core/Public/javascripts/iliad_ie_history.html b/iliad-stable/Core/Public/javascripts/iliad_ie_history.html deleted file mode 100644 index 392591d..0000000 --- a/iliad-stable/Core/Public/javascripts/iliad_ie_history.html +++ /dev/null @@ -1,12 +0,0 @@ - - - - - - - - diff --git a/iliad-stable/Core/Public/javascripts/jquery-1.8.3.min.js b/iliad-stable/Core/Public/javascripts/jquery-1.8.3.min.js deleted file mode 100644 index 83589da..0000000 --- a/iliad-stable/Core/Public/javascripts/jquery-1.8.3.min.js +++ /dev/null @@ -1,2 +0,0 @@ -/*! jQuery v1.8.3 jquery.com | jquery.org/license */ -(function(e,t){function _(e){var t=M[e]={};return v.each(e.split(y),function(e,n){t[n]=!0}),t}function H(e,n,r){if(r===t&&e.nodeType===1){var i="data-"+n.replace(P,"-$1").toLowerCase();r=e.getAttribute(i);if(typeof r=="string"){try{r=r==="true"?!0:r==="false"?!1:r==="null"?null:+r+""===r?+r:D.test(r)?v.parseJSON(r):r}catch(s){}v.data(e,n,r)}else r=t}return r}function B(e){var t;for(t in e){if(t==="data"&&v.isEmptyObject(e[t]))continue;if(t!=="toJSON")return!1}return!0}function et(){return!1}function tt(){return!0}function ut(e){return!e||!e.parentNode||e.parentNode.nodeType===11}function at(e,t){do e=e[t];while(e&&e.nodeType!==1);return e}function ft(e,t,n){t=t||0;if(v.isFunction(t))return v.grep(e,function(e,r){var i=!!t.call(e,r,e);return i===n});if(t.nodeType)return v.grep(e,function(e,r){return e===t===n});if(typeof t=="string"){var r=v.grep(e,function(e){return e.nodeType===1});if(it.test(t))return v.filter(t,r,!n);t=v.filter(t,r)}return v.grep(e,function(e,r){return v.inArray(e,t)>=0===n})}function lt(e){var t=ct.split("|"),n=e.createDocumentFragment();if(n.createElement)while(t.length)n.createElement(t.pop());return n}function Lt(e,t){return e.getElementsByTagName(t)[0]||e.appendChild(e.ownerDocument.createElement(t))}function At(e,t){if(t.nodeType!==1||!v.hasData(e))return;var n,r,i,s=v._data(e),o=v._data(t,s),u=s.events;if(u){delete o.handle,o.events={};for(n in u)for(r=0,i=u[n].length;r").appendTo(i.body),n=t.css("display");t.remove();if(n==="none"||n===""){Pt=i.body.appendChild(Pt||v.extend(i.createElement("iframe"),{frameBorder:0,width:0,height:0}));if(!Ht||!Pt.createElement)Ht=(Pt.contentWindow||Pt.contentDocument).document,Ht.write(""),Ht.close();t=Ht.body.appendChild(Ht.createElement(e)),n=Dt(t,"display"),i.body.removeChild(Pt)}return Wt[e]=n,n}function fn(e,t,n,r){var i;if(v.isArray(t))v.each(t,function(t,i){n||sn.test(e)?r(e,i):fn(e+"["+(typeof i=="object"?t:"")+"]",i,n,r)});else if(!n&&v.type(t)==="object")for(i in t)fn(e+"["+i+"]",t[i],n,r);else r(e,t)}function Cn(e){return function(t,n){typeof t!="string"&&(n=t,t="*");var r,i,s,o=t.toLowerCase().split(y),u=0,a=o.length;if(v.isFunction(n))for(;u)[^>]*$|#([\w\-]*)$)/,E=/^<(\w+)\s*\/?>(?:<\/\1>|)$/,S=/^[\],:{}\s]*$/,x=/(?:^|:|,)(?:\s*\[)+/g,T=/\\(?:["\\\/bfnrt]|u[\da-fA-F]{4})/g,N=/"[^"\\\r\n]*"|true|false|null|-?(?:\d\d*\.|)\d+(?:[eE][\-+]?\d+|)/g,C=/^-ms-/,k=/-([\da-z])/gi,L=function(e,t){return(t+"").toUpperCase()},A=function(){i.addEventListener?(i.removeEventListener("DOMContentLoaded",A,!1),v.ready()):i.readyState==="complete"&&(i.detachEvent("onreadystatechange",A),v.ready())},O={};v.fn=v.prototype={constructor:v,init:function(e,n,r){var s,o,u,a;if(!e)return this;if(e.nodeType)return this.context=this[0]=e,this.length=1,this;if(typeof e=="string"){e.charAt(0)==="<"&&e.charAt(e.length-1)===">"&&e.length>=3?s=[null,e,null]:s=w.exec(e);if(s&&(s[1]||!n)){if(s[1])return n=n instanceof v?n[0]:n,a=n&&n.nodeType?n.ownerDocument||n:i,e=v.parseHTML(s[1],a,!0),E.test(s[1])&&v.isPlainObject(n)&&this.attr.call(e,n,!0),v.merge(this,e);o=i.getElementById(s[2]);if(o&&o.parentNode){if(o.id!==s[2])return r.find(e);this.length=1,this[0]=o}return this.context=i,this.selector=e,this}return!n||n.jquery?(n||r).find(e):this.constructor(n).find(e)}return v.isFunction(e)?r.ready(e):(e.selector!==t&&(this.selector=e.selector,this.context=e.context),v.makeArray(e,this))},selector:"",jquery:"1.8.3",length:0,size:function(){return this.length},toArray:function(){return l.call(this)},get:function(e){return e==null?this.toArray():e<0?this[this.length+e]:this[e]},pushStack:function(e,t,n){var r=v.merge(this.constructor(),e);return r.prevObject=this,r.context=this.context,t==="find"?r.selector=this.selector+(this.selector?" ":"")+n:t&&(r.selector=this.selector+"."+t+"("+n+")"),r},each:function(e,t){return v.each(this,e,t)},ready:function(e){return v.ready.promise().done(e),this},eq:function(e){return e=+e,e===-1?this.slice(e):this.slice(e,e+1)},first:function(){return this.eq(0)},last:function(){return this.eq(-1)},slice:function(){return this.pushStack(l.apply(this,arguments),"slice",l.call(arguments).join(","))},map:function(e){return this.pushStack(v.map(this,function(t,n){return e.call(t,n,t)}))},end:function(){return this.prevObject||this.constructor(null)},push:f,sort:[].sort,splice:[].splice},v.fn.init.prototype=v.fn,v.extend=v.fn.extend=function(){var e,n,r,i,s,o,u=arguments[0]||{},a=1,f=arguments.length,l=!1;typeof u=="boolean"&&(l=u,u=arguments[1]||{},a=2),typeof u!="object"&&!v.isFunction(u)&&(u={}),f===a&&(u=this,--a);for(;a0)return;r.resolveWith(i,[v]),v.fn.trigger&&v(i).trigger("ready").off("ready")},isFunction:function(e){return v.type(e)==="function"},isArray:Array.isArray||function(e){return v.type(e)==="array"},isWindow:function(e){return e!=null&&e==e.window},isNumeric:function(e){return!isNaN(parseFloat(e))&&isFinite(e)},type:function(e){return e==null?String(e):O[h.call(e)]||"object"},isPlainObject:function(e){if(!e||v.type(e)!=="object"||e.nodeType||v.isWindow(e))return!1;try{if(e.constructor&&!p.call(e,"constructor")&&!p.call(e.constructor.prototype,"isPrototypeOf"))return!1}catch(n){return!1}var r;for(r in e);return r===t||p.call(e,r)},isEmptyObject:function(e){var t;for(t in e)return!1;return!0},error:function(e){throw new Error(e)},parseHTML:function(e,t,n){var r;return!e||typeof e!="string"?null:(typeof t=="boolean"&&(n=t,t=0),t=t||i,(r=E.exec(e))?[t.createElement(r[1])]:(r=v.buildFragment([e],t,n?null:[]),v.merge([],(r.cacheable?v.clone(r.fragment):r.fragment).childNodes)))},parseJSON:function(t){if(!t||typeof t!="string")return null;t=v.trim(t);if(e.JSON&&e.JSON.parse)return e.JSON.parse(t);if(S.test(t.replace(T,"@").replace(N,"]").replace(x,"")))return(new Function("return "+t))();v.error("Invalid JSON: "+t)},parseXML:function(n){var r,i;if(!n||typeof n!="string")return null;try{e.DOMParser?(i=new DOMParser,r=i.parseFromString(n,"text/xml")):(r=new ActiveXObject("Microsoft.XMLDOM"),r.async="false",r.loadXML(n))}catch(s){r=t}return(!r||!r.documentElement||r.getElementsByTagName("parsererror").length)&&v.error("Invalid XML: "+n),r},noop:function(){},globalEval:function(t){t&&g.test(t)&&(e.execScript||function(t){e.eval.call(e,t)})(t)},camelCase:function(e){return e.replace(C,"ms-").replace(k,L)},nodeName:function(e,t){return e.nodeName&&e.nodeName.toLowerCase()===t.toLowerCase()},each:function(e,n,r){var i,s=0,o=e.length,u=o===t||v.isFunction(e);if(r){if(u){for(i in e)if(n.apply(e[i],r)===!1)break}else for(;s0&&e[0]&&e[a-1]||a===0||v.isArray(e));if(f)for(;u-1)a.splice(n,1),i&&(n<=o&&o--,n<=u&&u--)}),this},has:function(e){return v.inArray(e,a)>-1},empty:function(){return a=[],this},disable:function(){return a=f=n=t,this},disabled:function(){return!a},lock:function(){return f=t,n||c.disable(),this},locked:function(){return!f},fireWith:function(e,t){return t=t||[],t=[e,t.slice?t.slice():t],a&&(!r||f)&&(i?f.push(t):l(t)),this},fire:function(){return c.fireWith(this,arguments),this},fired:function(){return!!r}};return c},v.extend({Deferred:function(e){var t=[["resolve","done",v.Callbacks("once memory"),"resolved"],["reject","fail",v.Callbacks("once memory"),"rejected"],["notify","progress",v.Callbacks("memory")]],n="pending",r={state:function(){return n},always:function(){return i.done(arguments).fail(arguments),this},then:function(){var e=arguments;return v.Deferred(function(n){v.each(t,function(t,r){var s=r[0],o=e[t];i[r[1]](v.isFunction(o)?function(){var e=o.apply(this,arguments);e&&v.isFunction(e.promise)?e.promise().done(n.resolve).fail(n.reject).progress(n.notify):n[s+"With"](this===i?n:this,[e])}:n[s])}),e=null}).promise()},promise:function(e){return e!=null?v.extend(e,r):r}},i={};return r.pipe=r.then,v.each(t,function(e,s){var o=s[2],u=s[3];r[s[1]]=o.add,u&&o.add(function(){n=u},t[e^1][2].disable,t[2][2].lock),i[s[0]]=o.fire,i[s[0]+"With"]=o.fireWith}),r.promise(i),e&&e.call(i,i),i},when:function(e){var t=0,n=l.call(arguments),r=n.length,i=r!==1||e&&v.isFunction(e.promise)?r:0,s=i===1?e:v.Deferred(),o=function(e,t,n){return function(r){t[e]=this,n[e]=arguments.length>1?l.call(arguments):r,n===u?s.notifyWith(t,n):--i||s.resolveWith(t,n)}},u,a,f;if(r>1){u=new Array(r),a=new Array(r),f=new Array(r);for(;t
a",n=p.getElementsByTagName("*"),r=p.getElementsByTagName("a")[0];if(!n||!r||!n.length)return{};s=i.createElement("select"),o=s.appendChild(i.createElement("option")),u=p.getElementsByTagName("input")[0],r.style.cssText="top:1px;float:left;opacity:.5",t={leadingWhitespace:p.firstChild.nodeType===3,tbody:!p.getElementsByTagName("tbody").length,htmlSerialize:!!p.getElementsByTagName("link").length,style:/top/.test(r.getAttribute("style")),hrefNormalized:r.getAttribute("href")==="/a",opacity:/^0.5/.test(r.style.opacity),cssFloat:!!r.style.cssFloat,checkOn:u.value==="on",optSelected:o.selected,getSetAttribute:p.className!=="t",enctype:!!i.createElement("form").enctype,html5Clone:i.createElement("nav").cloneNode(!0).outerHTML!=="<:nav>",boxModel:i.compatMode==="CSS1Compat",submitBubbles:!0,changeBubbles:!0,focusinBubbles:!1,deleteExpando:!0,noCloneEvent:!0,inlineBlockNeedsLayout:!1,shrinkWrapBlocks:!1,reliableMarginRight:!0,boxSizingReliable:!0,pixelPosition:!1},u.checked=!0,t.noCloneChecked=u.cloneNode(!0).checked,s.disabled=!0,t.optDisabled=!o.disabled;try{delete p.test}catch(d){t.deleteExpando=!1}!p.addEventListener&&p.attachEvent&&p.fireEvent&&(p.attachEvent("onclick",h=function(){t.noCloneEvent=!1}),p.cloneNode(!0).fireEvent("onclick"),p.detachEvent("onclick",h)),u=i.createElement("input"),u.value="t",u.setAttribute("type","radio"),t.radioValue=u.value==="t",u.setAttribute("checked","checked"),u.setAttribute("name","t"),p.appendChild(u),a=i.createDocumentFragment(),a.appendChild(p.lastChild),t.checkClone=a.cloneNode(!0).cloneNode(!0).lastChild.checked,t.appendChecked=u.checked,a.removeChild(u),a.appendChild(p);if(p.attachEvent)for(l in{submit:!0,change:!0,focusin:!0})f="on"+l,c=f in p,c||(p.setAttribute(f,"return;"),c=typeof p[f]=="function"),t[l+"Bubbles"]=c;return v(function(){var n,r,s,o,u="padding:0;margin:0;border:0;display:block;overflow:hidden;",a=i.getElementsByTagName("body")[0];if(!a)return;n=i.createElement("div"),n.style.cssText="visibility:hidden;border:0;width:0;height:0;position:static;top:0;margin-top:1px",a.insertBefore(n,a.firstChild),r=i.createElement("div"),n.appendChild(r),r.innerHTML="
t
",s=r.getElementsByTagName("td"),s[0].style.cssText="padding:0;margin:0;border:0;display:none",c=s[0].offsetHeight===0,s[0].style.display="",s[1].style.display="none",t.reliableHiddenOffsets=c&&s[0].offsetHeight===0,r.innerHTML="",r.style.cssText="box-sizing:border-box;-moz-box-sizing:border-box;-webkit-box-sizing:border-box;padding:1px;border:1px;display:block;width:4px;margin-top:1%;position:absolute;top:1%;",t.boxSizing=r.offsetWidth===4,t.doesNotIncludeMarginInBodyOffset=a.offsetTop!==1,e.getComputedStyle&&(t.pixelPosition=(e.getComputedStyle(r,null)||{}).top!=="1%",t.boxSizingReliable=(e.getComputedStyle(r,null)||{width:"4px"}).width==="4px",o=i.createElement("div"),o.style.cssText=r.style.cssText=u,o.style.marginRight=o.style.width="0",r.style.width="1px",r.appendChild(o),t.reliableMarginRight=!parseFloat((e.getComputedStyle(o,null)||{}).marginRight)),typeof r.style.zoom!="undefined"&&(r.innerHTML="",r.style.cssText=u+"width:1px;padding:1px;display:inline;zoom:1",t.inlineBlockNeedsLayout=r.offsetWidth===3,r.style.display="block",r.style.overflow="visible",r.innerHTML="
",r.firstChild.style.width="5px",t.shrinkWrapBlocks=r.offsetWidth!==3,n.style.zoom=1),a.removeChild(n),n=r=s=o=null}),a.removeChild(p),n=r=s=o=u=a=p=null,t}();var D=/(?:\{[\s\S]*\}|\[[\s\S]*\])$/,P=/([A-Z])/g;v.extend({cache:{},deletedIds:[],uuid:0,expando:"jQuery"+(v.fn.jquery+Math.random()).replace(/\D/g,""),noData:{embed:!0,object:"clsid:D27CDB6E-AE6D-11cf-96B8-444553540000",applet:!0},hasData:function(e){return e=e.nodeType?v.cache[e[v.expando]]:e[v.expando],!!e&&!B(e)},data:function(e,n,r,i){if(!v.acceptData(e))return;var s,o,u=v.expando,a=typeof n=="string",f=e.nodeType,l=f?v.cache:e,c=f?e[u]:e[u]&&u;if((!c||!l[c]||!i&&!l[c].data)&&a&&r===t)return;c||(f?e[u]=c=v.deletedIds.pop()||v.guid++:c=u),l[c]||(l[c]={},f||(l[c].toJSON=v.noop));if(typeof n=="object"||typeof n=="function")i?l[c]=v.extend(l[c],n):l[c].data=v.extend(l[c].data,n);return s=l[c],i||(s.data||(s.data={}),s=s.data),r!==t&&(s[v.camelCase(n)]=r),a?(o=s[n],o==null&&(o=s[v.camelCase(n)])):o=s,o},removeData:function(e,t,n){if(!v.acceptData(e))return;var r,i,s,o=e.nodeType,u=o?v.cache:e,a=o?e[v.expando]:v.expando;if(!u[a])return;if(t){r=n?u[a]:u[a].data;if(r){v.isArray(t)||(t in r?t=[t]:(t=v.camelCase(t),t in r?t=[t]:t=t.split(" ")));for(i=0,s=t.length;i1,null,!1))},removeData:function(e){return this.each(function(){v.removeData(this,e)})}}),v.extend({queue:function(e,t,n){var r;if(e)return t=(t||"fx")+"queue",r=v._data(e,t),n&&(!r||v.isArray(n)?r=v._data(e,t,v.makeArray(n)):r.push(n)),r||[]},dequeue:function(e,t){t=t||"fx";var n=v.queue(e,t),r=n.length,i=n.shift(),s=v._queueHooks(e,t),o=function(){v.dequeue(e,t)};i==="inprogress"&&(i=n.shift(),r--),i&&(t==="fx"&&n.unshift("inprogress"),delete s.stop,i.call(e,o,s)),!r&&s&&s.empty.fire()},_queueHooks:function(e,t){var n=t+"queueHooks";return v._data(e,n)||v._data(e,n,{empty:v.Callbacks("once memory").add(function(){v.removeData(e,t+"queue",!0),v.removeData(e,n,!0)})})}}),v.fn.extend({queue:function(e,n){var r=2;return typeof e!="string"&&(n=e,e="fx",r--),arguments.length1)},removeAttr:function(e){return this.each(function(){v.removeAttr(this,e)})},prop:function(e,t){return v.access(this,v.prop,e,t,arguments.length>1)},removeProp:function(e){return e=v.propFix[e]||e,this.each(function(){try{this[e]=t,delete this[e]}catch(n){}})},addClass:function(e){var t,n,r,i,s,o,u;if(v.isFunction(e))return this.each(function(t){v(this).addClass(e.call(this,t,this.className))});if(e&&typeof e=="string"){t=e.split(y);for(n=0,r=this.length;n=0)r=r.replace(" "+n[s]+" "," ");i.className=e?v.trim(r):""}}}return this},toggleClass:function(e,t){var n=typeof e,r=typeof t=="boolean";return v.isFunction(e)?this.each(function(n){v(this).toggleClass(e.call(this,n,this.className,t),t)}):this.each(function(){if(n==="string"){var i,s=0,o=v(this),u=t,a=e.split(y);while(i=a[s++])u=r?u:!o.hasClass(i),o[u?"addClass":"removeClass"](i)}else if(n==="undefined"||n==="boolean")this.className&&v._data(this,"__className__",this.className),this.className=this.className||e===!1?"":v._data(this,"__className__")||""})},hasClass:function(e){var t=" "+e+" ",n=0,r=this.length;for(;n=0)return!0;return!1},val:function(e){var n,r,i,s=this[0];if(!arguments.length){if(s)return n=v.valHooks[s.type]||v.valHooks[s.nodeName.toLowerCase()],n&&"get"in n&&(r=n.get(s,"value"))!==t?r:(r=s.value,typeof r=="string"?r.replace(R,""):r==null?"":r);return}return i=v.isFunction(e),this.each(function(r){var s,o=v(this);if(this.nodeType!==1)return;i?s=e.call(this,r,o.val()):s=e,s==null?s="":typeof s=="number"?s+="":v.isArray(s)&&(s=v.map(s,function(e){return e==null?"":e+""})),n=v.valHooks[this.type]||v.valHooks[this.nodeName.toLowerCase()];if(!n||!("set"in n)||n.set(this,s,"value")===t)this.value=s})}}),v.extend({valHooks:{option:{get:function(e){var t=e.attributes.value;return!t||t.specified?e.value:e.text}},select:{get:function(e){var t,n,r=e.options,i=e.selectedIndex,s=e.type==="select-one"||i<0,o=s?null:[],u=s?i+1:r.length,a=i<0?u:s?i:0;for(;a=0}),n.length||(e.selectedIndex=-1),n}}},attrFn:{},attr:function(e,n,r,i){var s,o,u,a=e.nodeType;if(!e||a===3||a===8||a===2)return;if(i&&v.isFunction(v.fn[n]))return v(e)[n](r);if(typeof e.getAttribute=="undefined")return v.prop(e,n,r);u=a!==1||!v.isXMLDoc(e),u&&(n=n.toLowerCase(),o=v.attrHooks[n]||(X.test(n)?F:j));if(r!==t){if(r===null){v.removeAttr(e,n);return}return o&&"set"in o&&u&&(s=o.set(e,r,n))!==t?s:(e.setAttribute(n,r+""),r)}return o&&"get"in o&&u&&(s=o.get(e,n))!==null?s:(s=e.getAttribute(n),s===null?t:s)},removeAttr:function(e,t){var n,r,i,s,o=0;if(t&&e.nodeType===1){r=t.split(y);for(;o=0}})});var $=/^(?:textarea|input|select)$/i,J=/^([^\.]*|)(?:\.(.+)|)$/,K=/(?:^|\s)hover(\.\S+|)\b/,Q=/^key/,G=/^(?:mouse|contextmenu)|click/,Y=/^(?:focusinfocus|focusoutblur)$/,Z=function(e){return v.event.special.hover?e:e.replace(K,"mouseenter$1 mouseleave$1")};v.event={add:function(e,n,r,i,s){var o,u,a,f,l,c,h,p,d,m,g;if(e.nodeType===3||e.nodeType===8||!n||!r||!(o=v._data(e)))return;r.handler&&(d=r,r=d.handler,s=d.selector),r.guid||(r.guid=v.guid++),a=o.events,a||(o.events=a={}),u=o.handle,u||(o.handle=u=function(e){return typeof v=="undefined"||!!e&&v.event.triggered===e.type?t:v.event.dispatch.apply(u.elem,arguments)},u.elem=e),n=v.trim(Z(n)).split(" ");for(f=0;f=0&&(y=y.slice(0,-1),a=!0),y.indexOf(".")>=0&&(b=y.split("."),y=b.shift(),b.sort());if((!s||v.event.customEvent[y])&&!v.event.global[y])return;n=typeof n=="object"?n[v.expando]?n:new v.Event(y,n):new v.Event(y),n.type=y,n.isTrigger=!0,n.exclusive=a,n.namespace=b.join("."),n.namespace_re=n.namespace?new RegExp("(^|\\.)"+b.join("\\.(?:.*\\.|)")+"(\\.|$)"):null,h=y.indexOf(":")<0?"on"+y:"";if(!s){u=v.cache;for(f in u)u[f].events&&u[f].events[y]&&v.event.trigger(n,r,u[f].handle.elem,!0);return}n.result=t,n.target||(n.target=s),r=r!=null?v.makeArray(r):[],r.unshift(n),p=v.event.special[y]||{};if(p.trigger&&p.trigger.apply(s,r)===!1)return;m=[[s,p.bindType||y]];if(!o&&!p.noBubble&&!v.isWindow(s)){g=p.delegateType||y,l=Y.test(g+y)?s:s.parentNode;for(c=s;l;l=l.parentNode)m.push([l,g]),c=l;c===(s.ownerDocument||i)&&m.push([c.defaultView||c.parentWindow||e,g])}for(f=0;f=0:v.find(h,this,null,[s]).length),u[h]&&f.push(c);f.length&&w.push({elem:s,matches:f})}d.length>m&&w.push({elem:this,matches:d.slice(m)});for(r=0;r0?this.on(t,null,e,n):this.trigger(t)},Q.test(t)&&(v.event.fixHooks[t]=v.event.keyHooks),G.test(t)&&(v.event.fixHooks[t]=v.event.mouseHooks)}),function(e,t){function nt(e,t,n,r){n=n||[],t=t||g;var i,s,a,f,l=t.nodeType;if(!e||typeof e!="string")return n;if(l!==1&&l!==9)return[];a=o(t);if(!a&&!r)if(i=R.exec(e))if(f=i[1]){if(l===9){s=t.getElementById(f);if(!s||!s.parentNode)return n;if(s.id===f)return n.push(s),n}else if(t.ownerDocument&&(s=t.ownerDocument.getElementById(f))&&u(t,s)&&s.id===f)return n.push(s),n}else{if(i[2])return S.apply(n,x.call(t.getElementsByTagName(e),0)),n;if((f=i[3])&&Z&&t.getElementsByClassName)return S.apply(n,x.call(t.getElementsByClassName(f),0)),n}return vt(e.replace(j,"$1"),t,n,r,a)}function rt(e){return function(t){var n=t.nodeName.toLowerCase();return n==="input"&&t.type===e}}function it(e){return function(t){var n=t.nodeName.toLowerCase();return(n==="input"||n==="button")&&t.type===e}}function st(e){return N(function(t){return t=+t,N(function(n,r){var i,s=e([],n.length,t),o=s.length;while(o--)n[i=s[o]]&&(n[i]=!(r[i]=n[i]))})})}function ot(e,t,n){if(e===t)return n;var r=e.nextSibling;while(r){if(r===t)return-1;r=r.nextSibling}return 1}function ut(e,t){var n,r,s,o,u,a,f,l=L[d][e+" "];if(l)return t?0:l.slice(0);u=e,a=[],f=i.preFilter;while(u){if(!n||(r=F.exec(u)))r&&(u=u.slice(r[0].length)||u),a.push(s=[]);n=!1;if(r=I.exec(u))s.push(n=new m(r.shift())),u=u.slice(n.length),n.type=r[0].replace(j," ");for(o in i.filter)(r=J[o].exec(u))&&(!f[o]||(r=f[o](r)))&&(s.push(n=new m(r.shift())),u=u.slice(n.length),n.type=o,n.matches=r);if(!n)break}return t?u.length:u?nt.error(e):L(e,a).slice(0)}function at(e,t,r){var i=t.dir,s=r&&t.dir==="parentNode",o=w++;return t.first?function(t,n,r){while(t=t[i])if(s||t.nodeType===1)return e(t,n,r)}:function(t,r,u){if(!u){var a,f=b+" "+o+" ",l=f+n;while(t=t[i])if(s||t.nodeType===1){if((a=t[d])===l)return t.sizset;if(typeof a=="string"&&a.indexOf(f)===0){if(t.sizset)return t}else{t[d]=l;if(e(t,r,u))return t.sizset=!0,t;t.sizset=!1}}}else while(t=t[i])if(s||t.nodeType===1)if(e(t,r,u))return t}}function ft(e){return e.length>1?function(t,n,r){var i=e.length;while(i--)if(!e[i](t,n,r))return!1;return!0}:e[0]}function lt(e,t,n,r,i){var s,o=[],u=0,a=e.length,f=t!=null;for(;u-1&&(s[f]=!(o[f]=c))}}else g=lt(g===o?g.splice(d,g.length):g),i?i(null,o,g,a):S.apply(o,g)})}function ht(e){var t,n,r,s=e.length,o=i.relative[e[0].type],u=o||i.relative[" "],a=o?1:0,f=at(function(e){return e===t},u,!0),l=at(function(e){return T.call(t,e)>-1},u,!0),h=[function(e,n,r){return!o&&(r||n!==c)||((t=n).nodeType?f(e,n,r):l(e,n,r))}];for(;a1&&ft(h),a>1&&e.slice(0,a-1).join("").replace(j,"$1"),n,a0,s=e.length>0,o=function(u,a,f,l,h){var p,d,v,m=[],y=0,w="0",x=u&&[],T=h!=null,N=c,C=u||s&&i.find.TAG("*",h&&a.parentNode||a),k=b+=N==null?1:Math.E;T&&(c=a!==g&&a,n=o.el);for(;(p=C[w])!=null;w++){if(s&&p){for(d=0;v=e[d];d++)if(v(p,a,f)){l.push(p);break}T&&(b=k,n=++o.el)}r&&((p=!v&&p)&&y--,u&&x.push(p))}y+=w;if(r&&w!==y){for(d=0;v=t[d];d++)v(x,m,a,f);if(u){if(y>0)while(w--)!x[w]&&!m[w]&&(m[w]=E.call(l));m=lt(m)}S.apply(l,m),T&&!u&&m.length>0&&y+t.length>1&&nt.uniqueSort(l)}return T&&(b=k,c=N),x};return o.el=0,r?N(o):o}function dt(e,t,n){var r=0,i=t.length;for(;r2&&(f=u[0]).type==="ID"&&t.nodeType===9&&!s&&i.relative[u[1].type]){t=i.find.ID(f.matches[0].replace($,""),t,s)[0];if(!t)return n;e=e.slice(u.shift().length)}for(o=J.POS.test(e)?-1:u.length-1;o>=0;o--){f=u[o];if(i.relative[l=f.type])break;if(c=i.find[l])if(r=c(f.matches[0].replace($,""),z.test(u[0].type)&&t.parentNode||t,s)){u.splice(o,1),e=r.length&&u.join("");if(!e)return S.apply(n,x.call(r,0)),n;break}}}return a(e,h)(r,t,s,n,z.test(e)),n}function mt(){}var n,r,i,s,o,u,a,f,l,c,h=!0,p="undefined",d=("sizcache"+Math.random()).replace(".",""),m=String,g=e.document,y=g.documentElement,b=0,w=0,E=[].pop,S=[].push,x=[].slice,T=[].indexOf||function(e){var t=0,n=this.length;for(;ti.cacheLength&&delete e[t.shift()],e[n+" "]=r},e)},k=C(),L=C(),A=C(),O="[\\x20\\t\\r\\n\\f]",M="(?:\\\\.|[-\\w]|[^\\x00-\\xa0])+",_=M.replace("w","w#"),D="([*^$|!~]?=)",P="\\["+O+"*("+M+")"+O+"*(?:"+D+O+"*(?:(['\"])((?:\\\\.|[^\\\\])*?)\\3|("+_+")|)|)"+O+"*\\]",H=":("+M+")(?:\\((?:(['\"])((?:\\\\.|[^\\\\])*?)\\2|([^()[\\]]*|(?:(?:"+P+")|[^:]|\\\\.)*|.*))\\)|)",B=":(even|odd|eq|gt|lt|nth|first|last)(?:\\("+O+"*((?:-\\d)?\\d*)"+O+"*\\)|)(?=[^-]|$)",j=new RegExp("^"+O+"+|((?:^|[^\\\\])(?:\\\\.)*)"+O+"+$","g"),F=new RegExp("^"+O+"*,"+O+"*"),I=new RegExp("^"+O+"*([\\x20\\t\\r\\n\\f>+~])"+O+"*"),q=new RegExp(H),R=/^(?:#([\w\-]+)|(\w+)|\.([\w\-]+))$/,U=/^:not/,z=/[\x20\t\r\n\f]*[+~]/,W=/:not\($/,X=/h\d/i,V=/input|select|textarea|button/i,$=/\\(?!\\)/g,J={ID:new RegExp("^#("+M+")"),CLASS:new RegExp("^\\.("+M+")"),NAME:new RegExp("^\\[name=['\"]?("+M+")['\"]?\\]"),TAG:new RegExp("^("+M.replace("w","w*")+")"),ATTR:new RegExp("^"+P),PSEUDO:new RegExp("^"+H),POS:new RegExp(B,"i"),CHILD:new RegExp("^:(only|nth|first|last)-child(?:\\("+O+"*(even|odd|(([+-]|)(\\d*)n|)"+O+"*(?:([+-]|)"+O+"*(\\d+)|))"+O+"*\\)|)","i"),needsContext:new RegExp("^"+O+"*[>+~]|"+B,"i")},K=function(e){var t=g.createElement("div");try{return e(t)}catch(n){return!1}finally{t=null}},Q=K(function(e){return e.appendChild(g.createComment("")),!e.getElementsByTagName("*").length}),G=K(function(e){return e.innerHTML="",e.firstChild&&typeof e.firstChild.getAttribute!==p&&e.firstChild.getAttribute("href")==="#"}),Y=K(function(e){e.innerHTML="";var t=typeof e.lastChild.getAttribute("multiple");return t!=="boolean"&&t!=="string"}),Z=K(function(e){return e.innerHTML="",!e.getElementsByClassName||!e.getElementsByClassName("e").length?!1:(e.lastChild.className="e",e.getElementsByClassName("e").length===2)}),et=K(function(e){e.id=d+0,e.innerHTML="
",y.insertBefore(e,y.firstChild);var t=g.getElementsByName&&g.getElementsByName(d).length===2+g.getElementsByName(d+0).length;return r=!g.getElementById(d),y.removeChild(e),t});try{x.call(y.childNodes,0)[0].nodeType}catch(tt){x=function(e){var t,n=[];for(;t=this[e];e++)n.push(t);return n}}nt.matches=function(e,t){return nt(e,null,null,t)},nt.matchesSelector=function(e,t){return nt(t,null,null,[e]).length>0},s=nt.getText=function(e){var t,n="",r=0,i=e.nodeType;if(i){if(i===1||i===9||i===11){if(typeof e.textContent=="string")return e.textContent;for(e=e.firstChild;e;e=e.nextSibling)n+=s(e)}else if(i===3||i===4)return e.nodeValue}else for(;t=e[r];r++)n+=s(t);return n},o=nt.isXML=function(e){var t=e&&(e.ownerDocument||e).documentElement;return t?t.nodeName!=="HTML":!1},u=nt.contains=y.contains?function(e,t){var n=e.nodeType===9?e.documentElement:e,r=t&&t.parentNode;return e===r||!!(r&&r.nodeType===1&&n.contains&&n.contains(r))}:y.compareDocumentPosition?function(e,t){return t&&!!(e.compareDocumentPosition(t)&16)}:function(e,t){while(t=t.parentNode)if(t===e)return!0;return!1},nt.attr=function(e,t){var n,r=o(e);return r||(t=t.toLowerCase()),(n=i.attrHandle[t])?n(e):r||Y?e.getAttribute(t):(n=e.getAttributeNode(t),n?typeof e[t]=="boolean"?e[t]?t:null:n.specified?n.value:null:null)},i=nt.selectors={cacheLength:50,createPseudo:N,match:J,attrHandle:G?{}:{href:function(e){return e.getAttribute("href",2)},type:function(e){return e.getAttribute("type")}},find:{ID:r?function(e,t,n){if(typeof t.getElementById!==p&&!n){var r=t.getElementById(e);return r&&r.parentNode?[r]:[]}}:function(e,n,r){if(typeof n.getElementById!==p&&!r){var i=n.getElementById(e);return i?i.id===e||typeof i.getAttributeNode!==p&&i.getAttributeNode("id").value===e?[i]:t:[]}},TAG:Q?function(e,t){if(typeof t.getElementsByTagName!==p)return t.getElementsByTagName(e)}:function(e,t){var n=t.getElementsByTagName(e);if(e==="*"){var r,i=[],s=0;for(;r=n[s];s++)r.nodeType===1&&i.push(r);return i}return n},NAME:et&&function(e,t){if(typeof t.getElementsByName!==p)return t.getElementsByName(name)},CLASS:Z&&function(e,t,n){if(typeof t.getElementsByClassName!==p&&!n)return t.getElementsByClassName(e)}},relative:{">":{dir:"parentNode",first:!0}," ":{dir:"parentNode"},"+":{dir:"previousSibling",first:!0},"~":{dir:"previousSibling"}},preFilter:{ATTR:function(e){return e[1]=e[1].replace($,""),e[3]=(e[4]||e[5]||"").replace($,""),e[2]==="~="&&(e[3]=" "+e[3]+" "),e.slice(0,4)},CHILD:function(e){return e[1]=e[1].toLowerCase(),e[1]==="nth"?(e[2]||nt.error(e[0]),e[3]=+(e[3]?e[4]+(e[5]||1):2*(e[2]==="even"||e[2]==="odd")),e[4]=+(e[6]+e[7]||e[2]==="odd")):e[2]&&nt.error(e[0]),e},PSEUDO:function(e){var t,n;if(J.CHILD.test(e[0]))return null;if(e[3])e[2]=e[3];else if(t=e[4])q.test(t)&&(n=ut(t,!0))&&(n=t.indexOf(")",t.length-n)-t.length)&&(t=t.slice(0,n),e[0]=e[0].slice(0,n)),e[2]=t;return e.slice(0,3)}},filter:{ID:r?function(e){return e=e.replace($,""),function(t){return t.getAttribute("id")===e}}:function(e){return e=e.replace($,""),function(t){var n=typeof t.getAttributeNode!==p&&t.getAttributeNode("id");return n&&n.value===e}},TAG:function(e){return e==="*"?function(){return!0}:(e=e.replace($,"").toLowerCase(),function(t){return t.nodeName&&t.nodeName.toLowerCase()===e})},CLASS:function(e){var t=k[d][e+" "];return t||(t=new RegExp("(^|"+O+")"+e+"("+O+"|$)"))&&k(e,function(e){return t.test(e.className||typeof e.getAttribute!==p&&e.getAttribute("class")||"")})},ATTR:function(e,t,n){return function(r,i){var s=nt.attr(r,e);return s==null?t==="!=":t?(s+="",t==="="?s===n:t==="!="?s!==n:t==="^="?n&&s.indexOf(n)===0:t==="*="?n&&s.indexOf(n)>-1:t==="$="?n&&s.substr(s.length-n.length)===n:t==="~="?(" "+s+" ").indexOf(n)>-1:t==="|="?s===n||s.substr(0,n.length+1)===n+"-":!1):!0}},CHILD:function(e,t,n,r){return e==="nth"?function(e){var t,i,s=e.parentNode;if(n===1&&r===0)return!0;if(s){i=0;for(t=s.firstChild;t;t=t.nextSibling)if(t.nodeType===1){i++;if(e===t)break}}return i-=r,i===n||i%n===0&&i/n>=0}:function(t){var n=t;switch(e){case"only":case"first":while(n=n.previousSibling)if(n.nodeType===1)return!1;if(e==="first")return!0;n=t;case"last":while(n=n.nextSibling)if(n.nodeType===1)return!1;return!0}}},PSEUDO:function(e,t){var n,r=i.pseudos[e]||i.setFilters[e.toLowerCase()]||nt.error("unsupported pseudo: "+e);return r[d]?r(t):r.length>1?(n=[e,e,"",t],i.setFilters.hasOwnProperty(e.toLowerCase())?N(function(e,n){var i,s=r(e,t),o=s.length;while(o--)i=T.call(e,s[o]),e[i]=!(n[i]=s[o])}):function(e){return r(e,0,n)}):r}},pseudos:{not:N(function(e){var t=[],n=[],r=a(e.replace(j,"$1"));return r[d]?N(function(e,t,n,i){var s,o=r(e,null,i,[]),u=e.length;while(u--)if(s=o[u])e[u]=!(t[u]=s)}):function(e,i,s){return t[0]=e,r(t,null,s,n),!n.pop()}}),has:N(function(e){return function(t){return nt(e,t).length>0}}),contains:N(function(e){return function(t){return(t.textContent||t.innerText||s(t)).indexOf(e)>-1}}),enabled:function(e){return e.disabled===!1},disabled:function(e){return e.disabled===!0},checked:function(e){var t=e.nodeName.toLowerCase();return t==="input"&&!!e.checked||t==="option"&&!!e.selected},selected:function(e){return e.parentNode&&e.parentNode.selectedIndex,e.selected===!0},parent:function(e){return!i.pseudos.empty(e)},empty:function(e){var t;e=e.firstChild;while(e){if(e.nodeName>"@"||(t=e.nodeType)===3||t===4)return!1;e=e.nextSibling}return!0},header:function(e){return X.test(e.nodeName)},text:function(e){var t,n;return e.nodeName.toLowerCase()==="input"&&(t=e.type)==="text"&&((n=e.getAttribute("type"))==null||n.toLowerCase()===t)},radio:rt("radio"),checkbox:rt("checkbox"),file:rt("file"),password:rt("password"),image:rt("image"),submit:it("submit"),reset:it("reset"),button:function(e){var t=e.nodeName.toLowerCase();return t==="input"&&e.type==="button"||t==="button"},input:function(e){return V.test(e.nodeName)},focus:function(e){var t=e.ownerDocument;return e===t.activeElement&&(!t.hasFocus||t.hasFocus())&&!!(e.type||e.href||~e.tabIndex)},active:function(e){return e===e.ownerDocument.activeElement},first:st(function(){return[0]}),last:st(function(e,t){return[t-1]}),eq:st(function(e,t,n){return[n<0?n+t:n]}),even:st(function(e,t){for(var n=0;n=0;)e.push(r);return e}),gt:st(function(e,t,n){for(var r=n<0?n+t:n;++r",e.querySelectorAll("[selected]").length||i.push("\\["+O+"*(?:checked|disabled|ismap|multiple|readonly|selected|value)"),e.querySelectorAll(":checked").length||i.push(":checked")}),K(function(e){e.innerHTML="

",e.querySelectorAll("[test^='']").length&&i.push("[*^$]="+O+"*(?:\"\"|'')"),e.innerHTML="",e.querySelectorAll(":enabled").length||i.push(":enabled",":disabled")}),i=new RegExp(i.join("|")),vt=function(e,r,s,o,u){if(!o&&!u&&!i.test(e)){var a,f,l=!0,c=d,h=r,p=r.nodeType===9&&e;if(r.nodeType===1&&r.nodeName.toLowerCase()!=="object"){a=ut(e),(l=r.getAttribute("id"))?c=l.replace(n,"\\$&"):r.setAttribute("id",c),c="[id='"+c+"'] ",f=a.length;while(f--)a[f]=c+a[f].join("");h=z.test(e)&&r.parentNode||r,p=a.join(",")}if(p)try{return S.apply(s,x.call(h.querySelectorAll(p),0)),s}catch(v){}finally{l||r.removeAttribute("id")}}return t(e,r,s,o,u)},u&&(K(function(t){e=u.call(t,"div");try{u.call(t,"[test!='']:sizzle"),s.push("!=",H)}catch(n){}}),s=new RegExp(s.join("|")),nt.matchesSelector=function(t,n){n=n.replace(r,"='$1']");if(!o(t)&&!s.test(n)&&!i.test(n))try{var a=u.call(t,n);if(a||e||t.document&&t.document.nodeType!==11)return a}catch(f){}return nt(n,null,null,[t]).length>0})}(),i.pseudos.nth=i.pseudos.eq,i.filters=mt.prototype=i.pseudos,i.setFilters=new mt,nt.attr=v.attr,v.find=nt,v.expr=nt.selectors,v.expr[":"]=v.expr.pseudos,v.unique=nt.uniqueSort,v.text=nt.getText,v.isXMLDoc=nt.isXML,v.contains=nt.contains}(e);var nt=/Until$/,rt=/^(?:parents|prev(?:Until|All))/,it=/^.[^:#\[\.,]*$/,st=v.expr.match.needsContext,ot={children:!0,contents:!0,next:!0,prev:!0};v.fn.extend({find:function(e){var t,n,r,i,s,o,u=this;if(typeof e!="string")return v(e).filter(function(){for(t=0,n=u.length;t0)for(i=r;i=0:v.filter(e,this).length>0:this.filter(e).length>0)},closest:function(e,t){var n,r=0,i=this.length,s=[],o=st.test(e)||typeof e!="string"?v(e,t||this.context):0;for(;r-1:v.find.matchesSelector(n,e)){s.push(n);break}n=n.parentNode}}return s=s.length>1?v.unique(s):s,this.pushStack(s,"closest",e)},index:function(e){return e?typeof e=="string"?v.inArray(this[0],v(e)):v.inArray(e.jquery?e[0]:e,this):this[0]&&this[0].parentNode?this.prevAll().length:-1},add:function(e,t){var n=typeof e=="string"?v(e,t):v.makeArray(e&&e.nodeType?[e]:e),r=v.merge(this.get(),n);return this.pushStack(ut(n[0])||ut(r[0])?r:v.unique(r))},addBack:function(e){return this.add(e==null?this.prevObject:this.prevObject.filter(e))}}),v.fn.andSelf=v.fn.addBack,v.each({parent:function(e){var t=e.parentNode;return t&&t.nodeType!==11?t:null},parents:function(e){return v.dir(e,"parentNode")},parentsUntil:function(e,t,n){return v.dir(e,"parentNode",n)},next:function(e){return at(e,"nextSibling")},prev:function(e){return at(e,"previousSibling")},nextAll:function(e){return v.dir(e,"nextSibling")},prevAll:function(e){return v.dir(e,"previousSibling")},nextUntil:function(e,t,n){return v.dir(e,"nextSibling",n)},prevUntil:function(e,t,n){return v.dir(e,"previousSibling",n)},siblings:function(e){return v.sibling((e.parentNode||{}).firstChild,e)},children:function(e){return v.sibling(e.firstChild)},contents:function(e){return v.nodeName(e,"iframe")?e.contentDocument||e.contentWindow.document:v.merge([],e.childNodes)}},function(e,t){v.fn[e]=function(n,r){var i=v.map(this,t,n);return nt.test(e)||(r=n),r&&typeof r=="string"&&(i=v.filter(r,i)),i=this.length>1&&!ot[e]?v.unique(i):i,this.length>1&&rt.test(e)&&(i=i.reverse()),this.pushStack(i,e,l.call(arguments).join(","))}}),v.extend({filter:function(e,t,n){return n&&(e=":not("+e+")"),t.length===1?v.find.matchesSelector(t[0],e)?[t[0]]:[]:v.find.matches(e,t)},dir:function(e,n,r){var i=[],s=e[n];while(s&&s.nodeType!==9&&(r===t||s.nodeType!==1||!v(s).is(r)))s.nodeType===1&&i.push(s),s=s[n];return i},sibling:function(e,t){var n=[];for(;e;e=e.nextSibling)e.nodeType===1&&e!==t&&n.push(e);return n}});var ct="abbr|article|aside|audio|bdi|canvas|data|datalist|details|figcaption|figure|footer|header|hgroup|mark|meter|nav|output|progress|section|summary|time|video",ht=/ jQuery\d+="(?:null|\d+)"/g,pt=/^\s+/,dt=/<(?!area|br|col|embed|hr|img|input|link|meta|param)(([\w:]+)[^>]*)\/>/gi,vt=/<([\w:]+)/,mt=/]","i"),Et=/^(?:checkbox|radio)$/,St=/checked\s*(?:[^=]|=\s*.checked.)/i,xt=/\/(java|ecma)script/i,Tt=/^\s*\s*$/g,Nt={option:[1,""],legend:[1,"
","
"],thead:[1,"","
"],tr:[2,"","
"],td:[3,"","
"],col:[2,"","
"],area:[1,"",""],_default:[0,"",""]},Ct=lt(i),kt=Ct.appendChild(i.createElement("div"));Nt.optgroup=Nt.option,Nt.tbody=Nt.tfoot=Nt.colgroup=Nt.caption=Nt.thead,Nt.th=Nt.td,v.support.htmlSerialize||(Nt._default=[1,"X
","
"]),v.fn.extend({text:function(e){return v.access(this,function(e){return e===t?v.text(this):this.empty().append((this[0]&&this[0].ownerDocument||i).createTextNode(e))},null,e,arguments.length)},wrapAll:function(e){if(v.isFunction(e))return this.each(function(t){v(this).wrapAll(e.call(this,t))});if(this[0]){var t=v(e,this[0].ownerDocument).eq(0).clone(!0);this[0].parentNode&&t.insertBefore(this[0]),t.map(function(){var e=this;while(e.firstChild&&e.firstChild.nodeType===1)e=e.firstChild;return e}).append(this)}return this},wrapInner:function(e){return v.isFunction(e)?this.each(function(t){v(this).wrapInner(e.call(this,t))}):this.each(function(){var t=v(this),n=t.contents();n.length?n.wrapAll(e):t.append(e)})},wrap:function(e){var t=v.isFunction(e);return this.each(function(n){v(this).wrapAll(t?e.call(this,n):e)})},unwrap:function(){return this.parent().each(function(){v.nodeName(this,"body")||v(this).replaceWith(this.childNodes)}).end()},append:function(){return this.domManip(arguments,!0,function(e){(this.nodeType===1||this.nodeType===11)&&this.appendChild(e)})},prepend:function(){return this.domManip(arguments,!0,function(e){(this.nodeType===1||this.nodeType===11)&&this.insertBefore(e,this.firstChild)})},before:function(){if(!ut(this[0]))return this.domManip(arguments,!1,function(e){this.parentNode.insertBefore(e,this)});if(arguments.length){var e=v.clean(arguments);return this.pushStack(v.merge(e,this),"before",this.selector)}},after:function(){if(!ut(this[0]))return this.domManip(arguments,!1,function(e){this.parentNode.insertBefore(e,this.nextSibling)});if(arguments.length){var e=v.clean(arguments);return this.pushStack(v.merge(this,e),"after",this.selector)}},remove:function(e,t){var n,r=0;for(;(n=this[r])!=null;r++)if(!e||v.filter(e,[n]).length)!t&&n.nodeType===1&&(v.cleanData(n.getElementsByTagName("*")),v.cleanData([n])),n.parentNode&&n.parentNode.removeChild(n);return this},empty:function(){var e,t=0;for(;(e=this[t])!=null;t++){e.nodeType===1&&v.cleanData(e.getElementsByTagName("*"));while(e.firstChild)e.removeChild(e.firstChild)}return this},clone:function(e,t){return e=e==null?!1:e,t=t==null?e:t,this.map(function(){return v.clone(this,e,t)})},html:function(e){return v.access(this,function(e){var n=this[0]||{},r=0,i=this.length;if(e===t)return n.nodeType===1?n.innerHTML.replace(ht,""):t;if(typeof e=="string"&&!yt.test(e)&&(v.support.htmlSerialize||!wt.test(e))&&(v.support.leadingWhitespace||!pt.test(e))&&!Nt[(vt.exec(e)||["",""])[1].toLowerCase()]){e=e.replace(dt,"<$1>");try{for(;r1&&typeof f=="string"&&St.test(f))return this.each(function(){v(this).domManip(e,n,r)});if(v.isFunction(f))return this.each(function(i){var s=v(this);e[0]=f.call(this,i,n?s.html():t),s.domManip(e,n,r)});if(this[0]){i=v.buildFragment(e,this,l),o=i.fragment,s=o.firstChild,o.childNodes.length===1&&(o=s);if(s){n=n&&v.nodeName(s,"tr");for(u=i.cacheable||c-1;a0?this.clone(!0):this).get(),v(o[i])[t](r),s=s.concat(r);return this.pushStack(s,e,o.selector)}}),v.extend({clone:function(e,t,n){var r,i,s,o;v.support.html5Clone||v.isXMLDoc(e)||!wt.test("<"+e.nodeName+">")?o=e.cloneNode(!0):(kt.innerHTML=e.outerHTML,kt.removeChild(o=kt.firstChild));if((!v.support.noCloneEvent||!v.support.noCloneChecked)&&(e.nodeType===1||e.nodeType===11)&&!v.isXMLDoc(e)){Ot(e,o),r=Mt(e),i=Mt(o);for(s=0;r[s];++s)i[s]&&Ot(r[s],i[s])}if(t){At(e,o);if(n){r=Mt(e),i=Mt(o);for(s=0;r[s];++s)At(r[s],i[s])}}return r=i=null,o},clean:function(e,t,n,r){var s,o,u,a,f,l,c,h,p,d,m,g,y=t===i&&Ct,b=[];if(!t||typeof t.createDocumentFragment=="undefined")t=i;for(s=0;(u=e[s])!=null;s++){typeof u=="number"&&(u+="");if(!u)continue;if(typeof u=="string")if(!gt.test(u))u=t.createTextNode(u);else{y=y||lt(t),c=t.createElement("div"),y.appendChild(c),u=u.replace(dt,"<$1>"),a=(vt.exec(u)||["",""])[1].toLowerCase(),f=Nt[a]||Nt._default,l=f[0],c.innerHTML=f[1]+u+f[2];while(l--)c=c.lastChild;if(!v.support.tbody){h=mt.test(u),p=a==="table"&&!h?c.firstChild&&c.firstChild.childNodes:f[1]===""&&!h?c.childNodes:[];for(o=p.length-1;o>=0;--o)v.nodeName(p[o],"tbody")&&!p[o].childNodes.length&&p[o].parentNode.removeChild(p[o])}!v.support.leadingWhitespace&&pt.test(u)&&c.insertBefore(t.createTextNode(pt.exec(u)[0]),c.firstChild),u=c.childNodes,c.parentNode.removeChild(c)}u.nodeType?b.push(u):v.merge(b,u)}c&&(u=c=y=null);if(!v.support.appendChecked)for(s=0;(u=b[s])!=null;s++)v.nodeName(u,"input")?_t(u):typeof u.getElementsByTagName!="undefined"&&v.grep(u.getElementsByTagName("input"),_t);if(n){m=function(e){if(!e.type||xt.test(e.type))return r?r.push(e.parentNode?e.parentNode.removeChild(e):e):n.appendChild(e)};for(s=0;(u=b[s])!=null;s++)if(!v.nodeName(u,"script")||!m(u))n.appendChild(u),typeof u.getElementsByTagName!="undefined"&&(g=v.grep(v.merge([],u.getElementsByTagName("script")),m),b.splice.apply(b,[s+1,0].concat(g)),s+=g.length)}return b},cleanData:function(e,t){var n,r,i,s,o=0,u=v.expando,a=v.cache,f=v.support.deleteExpando,l=v.event.special;for(;(i=e[o])!=null;o++)if(t||v.acceptData(i)){r=i[u],n=r&&a[r];if(n){if(n.events)for(s in n.events)l[s]?v.event.remove(i,s):v.removeEvent(i,s,n.handle);a[r]&&(delete a[r],f?delete i[u]:i.removeAttribute?i.removeAttribute(u):i[u]=null,v.deletedIds.push(r))}}}}),function(){var e,t;v.uaMatch=function(e){e=e.toLowerCase();var t=/(chrome)[ \/]([\w.]+)/.exec(e)||/(webkit)[ \/]([\w.]+)/.exec(e)||/(opera)(?:.*version|)[ \/]([\w.]+)/.exec(e)||/(msie) ([\w.]+)/.exec(e)||e.indexOf("compatible")<0&&/(mozilla)(?:.*? rv:([\w.]+)|)/.exec(e)||[];return{browser:t[1]||"",version:t[2]||"0"}},e=v.uaMatch(o.userAgent),t={},e.browser&&(t[e.browser]=!0,t.version=e.version),t.chrome?t.webkit=!0:t.webkit&&(t.safari=!0),v.browser=t,v.sub=function(){function e(t,n){return new e.fn.init(t,n)}v.extend(!0,e,this),e.superclass=this,e.fn=e.prototype=this(),e.fn.constructor=e,e.sub=this.sub,e.fn.init=function(r,i){return i&&i instanceof v&&!(i instanceof e)&&(i=e(i)),v.fn.init.call(this,r,i,t)},e.fn.init.prototype=e.fn;var t=e(i);return e}}();var Dt,Pt,Ht,Bt=/alpha\([^)]*\)/i,jt=/opacity=([^)]*)/,Ft=/^(top|right|bottom|left)$/,It=/^(none|table(?!-c[ea]).+)/,qt=/^margin/,Rt=new RegExp("^("+m+")(.*)$","i"),Ut=new RegExp("^("+m+")(?!px)[a-z%]+$","i"),zt=new RegExp("^([-+])=("+m+")","i"),Wt={BODY:"block"},Xt={position:"absolute",visibility:"hidden",display:"block"},Vt={letterSpacing:0,fontWeight:400},$t=["Top","Right","Bottom","Left"],Jt=["Webkit","O","Moz","ms"],Kt=v.fn.toggle;v.fn.extend({css:function(e,n){return v.access(this,function(e,n,r){return r!==t?v.style(e,n,r):v.css(e,n)},e,n,arguments.length>1)},show:function(){return Yt(this,!0)},hide:function(){return Yt(this)},toggle:function(e,t){var n=typeof e=="boolean";return v.isFunction(e)&&v.isFunction(t)?Kt.apply(this,arguments):this.each(function(){(n?e:Gt(this))?v(this).show():v(this).hide()})}}),v.extend({cssHooks:{opacity:{get:function(e,t){if(t){var n=Dt(e,"opacity");return n===""?"1":n}}}},cssNumber:{fillOpacity:!0,fontWeight:!0,lineHeight:!0,opacity:!0,orphans:!0,widows:!0,zIndex:!0,zoom:!0},cssProps:{"float":v.support.cssFloat?"cssFloat":"styleFloat"},style:function(e,n,r,i){if(!e||e.nodeType===3||e.nodeType===8||!e.style)return;var s,o,u,a=v.camelCase(n),f=e.style;n=v.cssProps[a]||(v.cssProps[a]=Qt(f,a)),u=v.cssHooks[n]||v.cssHooks[a];if(r===t)return u&&"get"in u&&(s=u.get(e,!1,i))!==t?s:f[n];o=typeof r,o==="string"&&(s=zt.exec(r))&&(r=(s[1]+1)*s[2]+parseFloat(v.css(e,n)),o="number");if(r==null||o==="number"&&isNaN(r))return;o==="number"&&!v.cssNumber[a]&&(r+="px");if(!u||!("set"in u)||(r=u.set(e,r,i))!==t)try{f[n]=r}catch(l){}},css:function(e,n,r,i){var s,o,u,a=v.camelCase(n);return n=v.cssProps[a]||(v.cssProps[a]=Qt(e.style,a)),u=v.cssHooks[n]||v.cssHooks[a],u&&"get"in u&&(s=u.get(e,!0,i)),s===t&&(s=Dt(e,n)),s==="normal"&&n in Vt&&(s=Vt[n]),r||i!==t?(o=parseFloat(s),r||v.isNumeric(o)?o||0:s):s},swap:function(e,t,n){var r,i,s={};for(i in t)s[i]=e.style[i],e.style[i]=t[i];r=n.call(e);for(i in t)e.style[i]=s[i];return r}}),e.getComputedStyle?Dt=function(t,n){var r,i,s,o,u=e.getComputedStyle(t,null),a=t.style;return u&&(r=u.getPropertyValue(n)||u[n],r===""&&!v.contains(t.ownerDocument,t)&&(r=v.style(t,n)),Ut.test(r)&&qt.test(n)&&(i=a.width,s=a.minWidth,o=a.maxWidth,a.minWidth=a.maxWidth=a.width=r,r=u.width,a.width=i,a.minWidth=s,a.maxWidth=o)),r}:i.documentElement.currentStyle&&(Dt=function(e,t){var n,r,i=e.currentStyle&&e.currentStyle[t],s=e.style;return i==null&&s&&s[t]&&(i=s[t]),Ut.test(i)&&!Ft.test(t)&&(n=s.left,r=e.runtimeStyle&&e.runtimeStyle.left,r&&(e.runtimeStyle.left=e.currentStyle.left),s.left=t==="fontSize"?"1em":i,i=s.pixelLeft+"px",s.left=n,r&&(e.runtimeStyle.left=r)),i===""?"auto":i}),v.each(["height","width"],function(e,t){v.cssHooks[t]={get:function(e,n,r){if(n)return e.offsetWidth===0&&It.test(Dt(e,"display"))?v.swap(e,Xt,function(){return tn(e,t,r)}):tn(e,t,r)},set:function(e,n,r){return Zt(e,n,r?en(e,t,r,v.support.boxSizing&&v.css(e,"boxSizing")==="border-box"):0)}}}),v.support.opacity||(v.cssHooks.opacity={get:function(e,t){return jt.test((t&&e.currentStyle?e.currentStyle.filter:e.style.filter)||"")?.01*parseFloat(RegExp.$1)+"":t?"1":""},set:function(e,t){var n=e.style,r=e.currentStyle,i=v.isNumeric(t)?"alpha(opacity="+t*100+")":"",s=r&&r.filter||n.filter||"";n.zoom=1;if(t>=1&&v.trim(s.replace(Bt,""))===""&&n.removeAttribute){n.removeAttribute("filter");if(r&&!r.filter)return}n.filter=Bt.test(s)?s.replace(Bt,i):s+" "+i}}),v(function(){v.support.reliableMarginRight||(v.cssHooks.marginRight={get:function(e,t){return v.swap(e,{display:"inline-block"},function(){if(t)return Dt(e,"marginRight")})}}),!v.support.pixelPosition&&v.fn.position&&v.each(["top","left"],function(e,t){v.cssHooks[t]={get:function(e,n){if(n){var r=Dt(e,t);return Ut.test(r)?v(e).position()[t]+"px":r}}}})}),v.expr&&v.expr.filters&&(v.expr.filters.hidden=function(e){return e.offsetWidth===0&&e.offsetHeight===0||!v.support.reliableHiddenOffsets&&(e.style&&e.style.display||Dt(e,"display"))==="none"},v.expr.filters.visible=function(e){return!v.expr.filters.hidden(e)}),v.each({margin:"",padding:"",border:"Width"},function(e,t){v.cssHooks[e+t]={expand:function(n){var r,i=typeof n=="string"?n.split(" "):[n],s={};for(r=0;r<4;r++)s[e+$t[r]+t]=i[r]||i[r-2]||i[0];return s}},qt.test(e)||(v.cssHooks[e+t].set=Zt)});var rn=/%20/g,sn=/\[\]$/,on=/\r?\n/g,un=/^(?:color|date|datetime|datetime-local|email|hidden|month|number|password|range|search|tel|text|time|url|week)$/i,an=/^(?:select|textarea)/i;v.fn.extend({serialize:function(){return v.param(this.serializeArray())},serializeArray:function(){return this.map(function(){return this.elements?v.makeArray(this.elements):this}).filter(function(){return this.name&&!this.disabled&&(this.checked||an.test(this.nodeName)||un.test(this.type))}).map(function(e,t){var n=v(this).val();return n==null?null:v.isArray(n)?v.map(n,function(e,n){return{name:t.name,value:e.replace(on,"\r\n")}}):{name:t.name,value:n.replace(on,"\r\n")}}).get()}}),v.param=function(e,n){var r,i=[],s=function(e,t){t=v.isFunction(t)?t():t==null?"":t,i[i.length]=encodeURIComponent(e)+"="+encodeURIComponent(t)};n===t&&(n=v.ajaxSettings&&v.ajaxSettings.traditional);if(v.isArray(e)||e.jquery&&!v.isPlainObject(e))v.each(e,function(){s(this.name,this.value)});else for(r in e)fn(r,e[r],n,s);return i.join("&").replace(rn,"+")};var ln,cn,hn=/#.*$/,pn=/^(.*?):[ \t]*([^\r\n]*)\r?$/mg,dn=/^(?:about|app|app\-storage|.+\-extension|file|res|widget):$/,vn=/^(?:GET|HEAD)$/,mn=/^\/\//,gn=/\?/,yn=/)<[^<]*)*<\/script>/gi,bn=/([?&])_=[^&]*/,wn=/^([\w\+\.\-]+:)(?:\/\/([^\/?#:]*)(?::(\d+)|)|)/,En=v.fn.load,Sn={},xn={},Tn=["*/"]+["*"];try{cn=s.href}catch(Nn){cn=i.createElement("a"),cn.href="",cn=cn.href}ln=wn.exec(cn.toLowerCase())||[],v.fn.load=function(e,n,r){if(typeof e!="string"&&En)return En.apply(this,arguments);if(!this.length)return this;var i,s,o,u=this,a=e.indexOf(" ");return a>=0&&(i=e.slice(a,e.length),e=e.slice(0,a)),v.isFunction(n)?(r=n,n=t):n&&typeof n=="object"&&(s="POST"),v.ajax({url:e,type:s,dataType:"html",data:n,complete:function(e,t){r&&u.each(r,o||[e.responseText,t,e])}}).done(function(e){o=arguments,u.html(i?v("
").append(e.replace(yn,"")).find(i):e)}),this},v.each("ajaxStart ajaxStop ajaxComplete ajaxError ajaxSuccess ajaxSend".split(" "),function(e,t){v.fn[t]=function(e){return this.on(t,e)}}),v.each(["get","post"],function(e,n){v[n]=function(e,r,i,s){return v.isFunction(r)&&(s=s||i,i=r,r=t),v.ajax({type:n,url:e,data:r,success:i,dataType:s})}}),v.extend({getScript:function(e,n){return v.get(e,t,n,"script")},getJSON:function(e,t,n){return v.get(e,t,n,"json")},ajaxSetup:function(e,t){return t?Ln(e,v.ajaxSettings):(t=e,e=v.ajaxSettings),Ln(e,t),e},ajaxSettings:{url:cn,isLocal:dn.test(ln[1]),global:!0,type:"GET",contentType:"application/x-www-form-urlencoded; charset=UTF-8",processData:!0,async:!0,accepts:{xml:"application/xml, text/xml",html:"text/html",text:"text/plain",json:"application/json, text/javascript","*":Tn},contents:{xml:/xml/,html:/html/,json:/json/},responseFields:{xml:"responseXML",text:"responseText"},converters:{"* text":e.String,"text html":!0,"text json":v.parseJSON,"text xml":v.parseXML},flatOptions:{context:!0,url:!0}},ajaxPrefilter:Cn(Sn),ajaxTransport:Cn(xn),ajax:function(e,n){function T(e,n,s,a){var l,y,b,w,S,T=n;if(E===2)return;E=2,u&&clearTimeout(u),o=t,i=a||"",x.readyState=e>0?4:0,s&&(w=An(c,x,s));if(e>=200&&e<300||e===304)c.ifModified&&(S=x.getResponseHeader("Last-Modified"),S&&(v.lastModified[r]=S),S=x.getResponseHeader("Etag"),S&&(v.etag[r]=S)),e===304?(T="notmodified",l=!0):(l=On(c,w),T=l.state,y=l.data,b=l.error,l=!b);else{b=T;if(!T||e)T="error",e<0&&(e=0)}x.status=e,x.statusText=(n||T)+"",l?d.resolveWith(h,[y,T,x]):d.rejectWith(h,[x,T,b]),x.statusCode(g),g=t,f&&p.trigger("ajax"+(l?"Success":"Error"),[x,c,l?y:b]),m.fireWith(h,[x,T]),f&&(p.trigger("ajaxComplete",[x,c]),--v.active||v.event.trigger("ajaxStop"))}typeof e=="object"&&(n=e,e=t),n=n||{};var r,i,s,o,u,a,f,l,c=v.ajaxSetup({},n),h=c.context||c,p=h!==c&&(h.nodeType||h instanceof v)?v(h):v.event,d=v.Deferred(),m=v.Callbacks("once memory"),g=c.statusCode||{},b={},w={},E=0,S="canceled",x={readyState:0,setRequestHeader:function(e,t){if(!E){var n=e.toLowerCase();e=w[n]=w[n]||e,b[e]=t}return this},getAllResponseHeaders:function(){return E===2?i:null},getResponseHeader:function(e){var n;if(E===2){if(!s){s={};while(n=pn.exec(i))s[n[1].toLowerCase()]=n[2]}n=s[e.toLowerCase()]}return n===t?null:n},overrideMimeType:function(e){return E||(c.mimeType=e),this},abort:function(e){return e=e||S,o&&o.abort(e),T(0,e),this}};d.promise(x),x.success=x.done,x.error=x.fail,x.complete=m.add,x.statusCode=function(e){if(e){var t;if(E<2)for(t in e)g[t]=[g[t],e[t]];else t=e[x.status],x.always(t)}return this},c.url=((e||c.url)+"").replace(hn,"").replace(mn,ln[1]+"//"),c.dataTypes=v.trim(c.dataType||"*").toLowerCase().split(y),c.crossDomain==null&&(a=wn.exec(c.url.toLowerCase()),c.crossDomain=!(!a||a[1]===ln[1]&&a[2]===ln[2]&&(a[3]||(a[1]==="http:"?80:443))==(ln[3]||(ln[1]==="http:"?80:443)))),c.data&&c.processData&&typeof c.data!="string"&&(c.data=v.param(c.data,c.traditional)),kn(Sn,c,n,x);if(E===2)return x;f=c.global,c.type=c.type.toUpperCase(),c.hasContent=!vn.test(c.type),f&&v.active++===0&&v.event.trigger("ajaxStart");if(!c.hasContent){c.data&&(c.url+=(gn.test(c.url)?"&":"?")+c.data,delete c.data),r=c.url;if(c.cache===!1){var N=v.now(),C=c.url.replace(bn,"$1_="+N);c.url=C+(C===c.url?(gn.test(c.url)?"&":"?")+"_="+N:"")}}(c.data&&c.hasContent&&c.contentType!==!1||n.contentType)&&x.setRequestHeader("Content-Type",c.contentType),c.ifModified&&(r=r||c.url,v.lastModified[r]&&x.setRequestHeader("If-Modified-Since",v.lastModified[r]),v.etag[r]&&x.setRequestHeader("If-None-Match",v.etag[r])),x.setRequestHeader("Accept",c.dataTypes[0]&&c.accepts[c.dataTypes[0]]?c.accepts[c.dataTypes[0]]+(c.dataTypes[0]!=="*"?", "+Tn+"; q=0.01":""):c.accepts["*"]);for(l in c.headers)x.setRequestHeader(l,c.headers[l]);if(!c.beforeSend||c.beforeSend.call(h,x,c)!==!1&&E!==2){S="abort";for(l in{success:1,error:1,complete:1})x[l](c[l]);o=kn(xn,c,n,x);if(!o)T(-1,"No Transport");else{x.readyState=1,f&&p.trigger("ajaxSend",[x,c]),c.async&&c.timeout>0&&(u=setTimeout(function(){x.abort("timeout")},c.timeout));try{E=1,o.send(b,T)}catch(k){if(!(E<2))throw k;T(-1,k)}}return x}return x.abort()},active:0,lastModified:{},etag:{}});var Mn=[],_n=/\?/,Dn=/(=)\?(?=&|$)|\?\?/,Pn=v.now();v.ajaxSetup({jsonp:"callback",jsonpCallback:function(){var e=Mn.pop()||v.expando+"_"+Pn++;return this[e]=!0,e}}),v.ajaxPrefilter("json jsonp",function(n,r,i){var s,o,u,a=n.data,f=n.url,l=n.jsonp!==!1,c=l&&Dn.test(f),h=l&&!c&&typeof a=="string"&&!(n.contentType||"").indexOf("application/x-www-form-urlencoded")&&Dn.test(a);if(n.dataTypes[0]==="jsonp"||c||h)return s=n.jsonpCallback=v.isFunction(n.jsonpCallback)?n.jsonpCallback():n.jsonpCallback,o=e[s],c?n.url=f.replace(Dn,"$1"+s):h?n.data=a.replace(Dn,"$1"+s):l&&(n.url+=(_n.test(f)?"&":"?")+n.jsonp+"="+s),n.converters["script json"]=function(){return u||v.error(s+" was not called"),u[0]},n.dataTypes[0]="json",e[s]=function(){u=arguments},i.always(function(){e[s]=o,n[s]&&(n.jsonpCallback=r.jsonpCallback,Mn.push(s)),u&&v.isFunction(o)&&o(u[0]),u=o=t}),"script"}),v.ajaxSetup({accepts:{script:"text/javascript, application/javascript, application/ecmascript, application/x-ecmascript"},contents:{script:/javascript|ecmascript/},converters:{"text script":function(e){return v.globalEval(e),e}}}),v.ajaxPrefilter("script",function(e){e.cache===t&&(e.cache=!1),e.crossDomain&&(e.type="GET",e.global=!1)}),v.ajaxTransport("script",function(e){if(e.crossDomain){var n,r=i.head||i.getElementsByTagName("head")[0]||i.documentElement;return{send:function(s,o){n=i.createElement("script"),n.async="async",e.scriptCharset&&(n.charset=e.scriptCharset),n.src=e.url,n.onload=n.onreadystatechange=function(e,i){if(i||!n.readyState||/loaded|complete/.test(n.readyState))n.onload=n.onreadystatechange=null,r&&n.parentNode&&r.removeChild(n),n=t,i||o(200,"success")},r.insertBefore(n,r.firstChild)},abort:function(){n&&n.onload(0,1)}}}});var Hn,Bn=e.ActiveXObject?function(){for(var e in Hn)Hn[e](0,1)}:!1,jn=0;v.ajaxSettings.xhr=e.ActiveXObject?function(){return!this.isLocal&&Fn()||In()}:Fn,function(e){v.extend(v.support,{ajax:!!e,cors:!!e&&"withCredentials"in e})}(v.ajaxSettings.xhr()),v.support.ajax&&v.ajaxTransport(function(n){if(!n.crossDomain||v.support.cors){var r;return{send:function(i,s){var o,u,a=n.xhr();n.username?a.open(n.type,n.url,n.async,n.username,n.password):a.open(n.type,n.url,n.async);if(n.xhrFields)for(u in n.xhrFields)a[u]=n.xhrFields[u];n.mimeType&&a.overrideMimeType&&a.overrideMimeType(n.mimeType),!n.crossDomain&&!i["X-Requested-With"]&&(i["X-Requested-With"]="XMLHttpRequest");try{for(u in i)a.setRequestHeader(u,i[u])}catch(f){}a.send(n.hasContent&&n.data||null),r=function(e,i){var u,f,l,c,h;try{if(r&&(i||a.readyState===4)){r=t,o&&(a.onreadystatechange=v.noop,Bn&&delete Hn[o]);if(i)a.readyState!==4&&a.abort();else{u=a.status,l=a.getAllResponseHeaders(),c={},h=a.responseXML,h&&h.documentElement&&(c.xml=h);try{c.text=a.responseText}catch(p){}try{f=a.statusText}catch(p){f=""}!u&&n.isLocal&&!n.crossDomain?u=c.text?200:404:u===1223&&(u=204)}}}catch(d){i||s(-1,d)}c&&s(u,f,c,l)},n.async?a.readyState===4?setTimeout(r,0):(o=++jn,Bn&&(Hn||(Hn={},v(e).unload(Bn)),Hn[o]=r),a.onreadystatechange=r):r()},abort:function(){r&&r(0,1)}}}});var qn,Rn,Un=/^(?:toggle|show|hide)$/,zn=new RegExp("^(?:([-+])=|)("+m+")([a-z%]*)$","i"),Wn=/queueHooks$/,Xn=[Gn],Vn={"*":[function(e,t){var n,r,i=this.createTween(e,t),s=zn.exec(t),o=i.cur(),u=+o||0,a=1,f=20;if(s){n=+s[2],r=s[3]||(v.cssNumber[e]?"":"px");if(r!=="px"&&u){u=v.css(i.elem,e,!0)||n||1;do a=a||".5",u/=a,v.style(i.elem,e,u+r);while(a!==(a=i.cur()/o)&&a!==1&&--f)}i.unit=r,i.start=u,i.end=s[1]?u+(s[1]+1)*n:n}return i}]};v.Animation=v.extend(Kn,{tweener:function(e,t){v.isFunction(e)?(t=e,e=["*"]):e=e.split(" ");var n,r=0,i=e.length;for(;r-1,f={},l={},c,h;a?(l=i.position(),c=l.top,h=l.left):(c=parseFloat(o)||0,h=parseFloat(u)||0),v.isFunction(t)&&(t=t.call(e,n,s)),t.top!=null&&(f.top=t.top-s.top+c),t.left!=null&&(f.left=t.left-s.left+h),"using"in t?t.using.call(e,f):i.css(f)}},v.fn.extend({position:function(){if(!this[0])return;var e=this[0],t=this.offsetParent(),n=this.offset(),r=er.test(t[0].nodeName)?{top:0,left:0}:t.offset();return n.top-=parseFloat(v.css(e,"marginTop"))||0,n.left-=parseFloat(v.css(e,"marginLeft"))||0,r.top+=parseFloat(v.css(t[0],"borderTopWidth"))||0,r.left+=parseFloat(v.css(t[0],"borderLeftWidth"))||0,{top:n.top-r.top,left:n.left-r.left}},offsetParent:function(){return this.map(function(){var e=this.offsetParent||i.body;while(e&&!er.test(e.nodeName)&&v.css(e,"position")==="static")e=e.offsetParent;return e||i.body})}}),v.each({scrollLeft:"pageXOffset",scrollTop:"pageYOffset"},function(e,n){var r=/Y/.test(n);v.fn[e]=function(i){return v.access(this,function(e,i,s){var o=tr(e);if(s===t)return o?n in o?o[n]:o.document.documentElement[i]:e[i];o?o.scrollTo(r?v(o).scrollLeft():s,r?s:v(o).scrollTop()):e[i]=s},e,i,arguments.length,null)}}),v.each({Height:"height",Width:"width"},function(e,n){v.each({padding:"inner"+e,content:n,"":"outer"+e},function(r,i){v.fn[i]=function(i,s){var o=arguments.length&&(r||typeof i!="boolean"),u=r||(i===!0||s===!0?"margin":"border");return v.access(this,function(n,r,i){var s;return v.isWindow(n)?n.document.documentElement["client"+e]:n.nodeType===9?(s=n.documentElement,Math.max(n.body["scroll"+e],s["scroll"+e],n.body["offset"+e],s["offset"+e],s["client"+e])):i===t?v.css(n,r,i,u):v.style(n,r,i,u)},n,o?i:t,o,null)}})}),e.jQuery=e.$=v,typeof define=="function"&&define.amd&&define.amd.jQuery&&define("jquery",[],function(){return v})})(window); \ No newline at end of file diff --git a/iliad-stable/Core/Public/javascripts/jquery-ui-1.9.2.js b/iliad-stable/Core/Public/javascripts/jquery-ui-1.9.2.js deleted file mode 100644 index 2f83e5a..0000000 --- a/iliad-stable/Core/Public/javascripts/jquery-ui-1.9.2.js +++ /dev/null @@ -1,14912 +0,0 @@ -/*! jQuery UI - v1.9.2 - 2012-11-23 -* http://jqueryui.com -* Includes: jquery.ui.core.js, jquery.ui.widget.js, jquery.ui.mouse.js, jquery.ui.draggable.js, jquery.ui.droppable.js, jquery.ui.resizable.js, jquery.ui.selectable.js, jquery.ui.sortable.js, jquery.ui.effect.js, jquery.ui.accordion.js, jquery.ui.autocomplete.js, jquery.ui.button.js, jquery.ui.datepicker.js, jquery.ui.dialog.js, jquery.ui.effect-blind.js, jquery.ui.effect-bounce.js, jquery.ui.effect-clip.js, jquery.ui.effect-drop.js, jquery.ui.effect-explode.js, jquery.ui.effect-fade.js, jquery.ui.effect-fold.js, jquery.ui.effect-highlight.js, jquery.ui.effect-pulsate.js, jquery.ui.effect-scale.js, jquery.ui.effect-shake.js, jquery.ui.effect-slide.js, jquery.ui.effect-transfer.js, jquery.ui.menu.js, jquery.ui.position.js, jquery.ui.progressbar.js, jquery.ui.slider.js, jquery.ui.spinner.js, jquery.ui.tabs.js, jquery.ui.tooltip.js -* Copyright 2012 jQuery Foundation and other contributors; Licensed MIT */ - -(function( $, undefined ) { - -var uuid = 0, - runiqueId = /^ui-id-\d+$/; - -// prevent duplicate loading -// this is only a problem because we proxy existing functions -// and we don't want to double proxy them -$.ui = $.ui || {}; -if ( $.ui.version ) { - return; -} - -$.extend( $.ui, { - version: "1.9.2", - - keyCode: { - BACKSPACE: 8, - COMMA: 188, - DELETE: 46, - DOWN: 40, - END: 35, - ENTER: 13, - ESCAPE: 27, - HOME: 36, - LEFT: 37, - NUMPAD_ADD: 107, - NUMPAD_DECIMAL: 110, - NUMPAD_DIVIDE: 111, - NUMPAD_ENTER: 108, - NUMPAD_MULTIPLY: 106, - NUMPAD_SUBTRACT: 109, - PAGE_DOWN: 34, - PAGE_UP: 33, - PERIOD: 190, - RIGHT: 39, - SPACE: 32, - TAB: 9, - UP: 38 - } -}); - -// plugins -$.fn.extend({ - _focus: $.fn.focus, - focus: function( delay, fn ) { - return typeof delay === "number" ? - this.each(function() { - var elem = this; - setTimeout(function() { - $( elem ).focus(); - if ( fn ) { - fn.call( elem ); - } - }, delay ); - }) : - this._focus.apply( this, arguments ); - }, - - scrollParent: function() { - var scrollParent; - if (($.ui.ie && (/(static|relative)/).test(this.css('position'))) || (/absolute/).test(this.css('position'))) { - scrollParent = this.parents().filter(function() { - return (/(relative|absolute|fixed)/).test($.css(this,'position')) && (/(auto|scroll)/).test($.css(this,'overflow')+$.css(this,'overflow-y')+$.css(this,'overflow-x')); - }).eq(0); - } else { - scrollParent = this.parents().filter(function() { - return (/(auto|scroll)/).test($.css(this,'overflow')+$.css(this,'overflow-y')+$.css(this,'overflow-x')); - }).eq(0); - } - - return (/fixed/).test(this.css('position')) || !scrollParent.length ? $(document) : scrollParent; - }, - - zIndex: function( zIndex ) { - if ( zIndex !== undefined ) { - return this.css( "zIndex", zIndex ); - } - - if ( this.length ) { - var elem = $( this[ 0 ] ), position, value; - while ( elem.length && elem[ 0 ] !== document ) { - // Ignore z-index if position is set to a value where z-index is ignored by the browser - // This makes behavior of this function consistent across browsers - // WebKit always returns auto if the element is positioned - position = elem.css( "position" ); - if ( position === "absolute" || position === "relative" || position === "fixed" ) { - // IE returns 0 when zIndex is not specified - // other browsers return a string - // we ignore the case of nested elements with an explicit value of 0 - //
- value = parseInt( elem.css( "zIndex" ), 10 ); - if ( !isNaN( value ) && value !== 0 ) { - return value; - } - } - elem = elem.parent(); - } - } - - return 0; - }, - - uniqueId: function() { - return this.each(function() { - if ( !this.id ) { - this.id = "ui-id-" + (++uuid); - } - }); - }, - - removeUniqueId: function() { - return this.each(function() { - if ( runiqueId.test( this.id ) ) { - $( this ).removeAttr( "id" ); - } - }); - } -}); - -// selectors -function focusable( element, isTabIndexNotNaN ) { - var map, mapName, img, - nodeName = element.nodeName.toLowerCase(); - if ( "area" === nodeName ) { - map = element.parentNode; - mapName = map.name; - if ( !element.href || !mapName || map.nodeName.toLowerCase() !== "map" ) { - return false; - } - img = $( "img[usemap=#" + mapName + "]" )[0]; - return !!img && visible( img ); - } - return ( /input|select|textarea|button|object/.test( nodeName ) ? - !element.disabled : - "a" === nodeName ? - element.href || isTabIndexNotNaN : - isTabIndexNotNaN) && - // the element and all of its ancestors must be visible - visible( element ); -} - -function visible( element ) { - return $.expr.filters.visible( element ) && - !$( element ).parents().andSelf().filter(function() { - return $.css( this, "visibility" ) === "hidden"; - }).length; -} - -$.extend( $.expr[ ":" ], { - data: $.expr.createPseudo ? - $.expr.createPseudo(function( dataName ) { - return function( elem ) { - return !!$.data( elem, dataName ); - }; - }) : - // support: jQuery <1.8 - function( elem, i, match ) { - return !!$.data( elem, match[ 3 ] ); - }, - - focusable: function( element ) { - return focusable( element, !isNaN( $.attr( element, "tabindex" ) ) ); - }, - - tabbable: function( element ) { - var tabIndex = $.attr( element, "tabindex" ), - isTabIndexNaN = isNaN( tabIndex ); - return ( isTabIndexNaN || tabIndex >= 0 ) && focusable( element, !isTabIndexNaN ); - } -}); - -// support -$(function() { - var body = document.body, - div = body.appendChild( div = document.createElement( "div" ) ); - - // access offsetHeight before setting the style to prevent a layout bug - // in IE 9 which causes the element to continue to take up space even - // after it is removed from the DOM (#8026) - div.offsetHeight; - - $.extend( div.style, { - minHeight: "100px", - height: "auto", - padding: 0, - borderWidth: 0 - }); - - $.support.minHeight = div.offsetHeight === 100; - $.support.selectstart = "onselectstart" in div; - - // set display to none to avoid a layout bug in IE - // http://dev.jquery.com/ticket/4014 - body.removeChild( div ).style.display = "none"; -}); - -// support: jQuery <1.8 -if ( !$( "" ).outerWidth( 1 ).jquery ) { - $.each( [ "Width", "Height" ], function( i, name ) { - var side = name === "Width" ? [ "Left", "Right" ] : [ "Top", "Bottom" ], - type = name.toLowerCase(), - orig = { - innerWidth: $.fn.innerWidth, - innerHeight: $.fn.innerHeight, - outerWidth: $.fn.outerWidth, - outerHeight: $.fn.outerHeight - }; - - function reduce( elem, size, border, margin ) { - $.each( side, function() { - size -= parseFloat( $.css( elem, "padding" + this ) ) || 0; - if ( border ) { - size -= parseFloat( $.css( elem, "border" + this + "Width" ) ) || 0; - } - if ( margin ) { - size -= parseFloat( $.css( elem, "margin" + this ) ) || 0; - } - }); - return size; - } - - $.fn[ "inner" + name ] = function( size ) { - if ( size === undefined ) { - return orig[ "inner" + name ].call( this ); - } - - return this.each(function() { - $( this ).css( type, reduce( this, size ) + "px" ); - }); - }; - - $.fn[ "outer" + name] = function( size, margin ) { - if ( typeof size !== "number" ) { - return orig[ "outer" + name ].call( this, size ); - } - - return this.each(function() { - $( this).css( type, reduce( this, size, true, margin ) + "px" ); - }); - }; - }); -} - -// support: jQuery 1.6.1, 1.6.2 (http://bugs.jquery.com/ticket/9413) -if ( $( "" ).data( "a-b", "a" ).removeData( "a-b" ).data( "a-b" ) ) { - $.fn.removeData = (function( removeData ) { - return function( key ) { - if ( arguments.length ) { - return removeData.call( this, $.camelCase( key ) ); - } else { - return removeData.call( this ); - } - }; - })( $.fn.removeData ); -} - - - - - -// deprecated - -(function() { - var uaMatch = /msie ([\w.]+)/.exec( navigator.userAgent.toLowerCase() ) || []; - $.ui.ie = uaMatch.length ? true : false; - $.ui.ie6 = parseFloat( uaMatch[ 1 ], 10 ) === 6; -})(); - -$.fn.extend({ - disableSelection: function() { - return this.bind( ( $.support.selectstart ? "selectstart" : "mousedown" ) + - ".ui-disableSelection", function( event ) { - event.preventDefault(); - }); - }, - - enableSelection: function() { - return this.unbind( ".ui-disableSelection" ); - } -}); - -$.extend( $.ui, { - // $.ui.plugin is deprecated. Use the proxy pattern instead. - plugin: { - add: function( module, option, set ) { - var i, - proto = $.ui[ module ].prototype; - for ( i in set ) { - proto.plugins[ i ] = proto.plugins[ i ] || []; - proto.plugins[ i ].push( [ option, set[ i ] ] ); - } - }, - call: function( instance, name, args ) { - var i, - set = instance.plugins[ name ]; - if ( !set || !instance.element[ 0 ].parentNode || instance.element[ 0 ].parentNode.nodeType === 11 ) { - return; - } - - for ( i = 0; i < set.length; i++ ) { - if ( instance.options[ set[ i ][ 0 ] ] ) { - set[ i ][ 1 ].apply( instance.element, args ); - } - } - } - }, - - contains: $.contains, - - // only used by resizable - hasScroll: function( el, a ) { - - //If overflow is hidden, the element might have extra content, but the user wants to hide it - if ( $( el ).css( "overflow" ) === "hidden") { - return false; - } - - var scroll = ( a && a === "left" ) ? "scrollLeft" : "scrollTop", - has = false; - - if ( el[ scroll ] > 0 ) { - return true; - } - - // TODO: determine which cases actually cause this to happen - // if the element doesn't have the scroll set, see if it's possible to - // set the scroll - el[ scroll ] = 1; - has = ( el[ scroll ] > 0 ); - el[ scroll ] = 0; - return has; - }, - - // these are odd functions, fix the API or move into individual plugins - isOverAxis: function( x, reference, size ) { - //Determines when x coordinate is over "b" element axis - return ( x > reference ) && ( x < ( reference + size ) ); - }, - isOver: function( y, x, top, left, height, width ) { - //Determines when x, y coordinates is over "b" element - return $.ui.isOverAxis( y, top, height ) && $.ui.isOverAxis( x, left, width ); - } -}); - -})( jQuery ); - -(function( $, undefined ) { - -var uuid = 0, - slice = Array.prototype.slice, - _cleanData = $.cleanData; -$.cleanData = function( elems ) { - for ( var i = 0, elem; (elem = elems[i]) != null; i++ ) { - try { - $( elem ).triggerHandler( "remove" ); - // http://bugs.jquery.com/ticket/8235 - } catch( e ) {} - } - _cleanData( elems ); -}; - -$.widget = function( name, base, prototype ) { - var fullName, existingConstructor, constructor, basePrototype, - namespace = name.split( "." )[ 0 ]; - - name = name.split( "." )[ 1 ]; - fullName = namespace + "-" + name; - - if ( !prototype ) { - prototype = base; - base = $.Widget; - } - - // create selector for plugin - $.expr[ ":" ][ fullName.toLowerCase() ] = function( elem ) { - return !!$.data( elem, fullName ); - }; - - $[ namespace ] = $[ namespace ] || {}; - existingConstructor = $[ namespace ][ name ]; - constructor = $[ namespace ][ name ] = function( options, element ) { - // allow instantiation without "new" keyword - if ( !this._createWidget ) { - return new constructor( options, element ); - } - - // allow instantiation without initializing for simple inheritance - // must use "new" keyword (the code above always passes args) - if ( arguments.length ) { - this._createWidget( options, element ); - } - }; - // extend with the existing constructor to carry over any static properties - $.extend( constructor, existingConstructor, { - version: prototype.version, - // copy the object used to create the prototype in case we need to - // redefine the widget later - _proto: $.extend( {}, prototype ), - // track widgets that inherit from this widget in case this widget is - // redefined after a widget inherits from it - _childConstructors: [] - }); - - basePrototype = new base(); - // we need to make the options hash a property directly on the new instance - // otherwise we'll modify the options hash on the prototype that we're - // inheriting from - basePrototype.options = $.widget.extend( {}, basePrototype.options ); - $.each( prototype, function( prop, value ) { - if ( $.isFunction( value ) ) { - prototype[ prop ] = (function() { - var _super = function() { - return base.prototype[ prop ].apply( this, arguments ); - }, - _superApply = function( args ) { - return base.prototype[ prop ].apply( this, args ); - }; - return function() { - var __super = this._super, - __superApply = this._superApply, - returnValue; - - this._super = _super; - this._superApply = _superApply; - - returnValue = value.apply( this, arguments ); - - this._super = __super; - this._superApply = __superApply; - - return returnValue; - }; - })(); - } - }); - constructor.prototype = $.widget.extend( basePrototype, { - // TODO: remove support for widgetEventPrefix - // always use the name + a colon as the prefix, e.g., draggable:start - // don't prefix for widgets that aren't DOM-based - widgetEventPrefix: existingConstructor ? basePrototype.widgetEventPrefix : name - }, prototype, { - constructor: constructor, - namespace: namespace, - widgetName: name, - // TODO remove widgetBaseClass, see #8155 - widgetBaseClass: fullName, - widgetFullName: fullName - }); - - // If this widget is being redefined then we need to find all widgets that - // are inheriting from it and redefine all of them so that they inherit from - // the new version of this widget. We're essentially trying to replace one - // level in the prototype chain. - if ( existingConstructor ) { - $.each( existingConstructor._childConstructors, function( i, child ) { - var childPrototype = child.prototype; - - // redefine the child widget using the same prototype that was - // originally used, but inherit from the new version of the base - $.widget( childPrototype.namespace + "." + childPrototype.widgetName, constructor, child._proto ); - }); - // remove the list of existing child constructors from the old constructor - // so the old child constructors can be garbage collected - delete existingConstructor._childConstructors; - } else { - base._childConstructors.push( constructor ); - } - - $.widget.bridge( name, constructor ); -}; - -$.widget.extend = function( target ) { - var input = slice.call( arguments, 1 ), - inputIndex = 0, - inputLength = input.length, - key, - value; - for ( ; inputIndex < inputLength; inputIndex++ ) { - for ( key in input[ inputIndex ] ) { - value = input[ inputIndex ][ key ]; - if ( input[ inputIndex ].hasOwnProperty( key ) && value !== undefined ) { - // Clone objects - if ( $.isPlainObject( value ) ) { - target[ key ] = $.isPlainObject( target[ key ] ) ? - $.widget.extend( {}, target[ key ], value ) : - // Don't extend strings, arrays, etc. with objects - $.widget.extend( {}, value ); - // Copy everything else by reference - } else { - target[ key ] = value; - } - } - } - } - return target; -}; - -$.widget.bridge = function( name, object ) { - var fullName = object.prototype.widgetFullName || name; - $.fn[ name ] = function( options ) { - var isMethodCall = typeof options === "string", - args = slice.call( arguments, 1 ), - returnValue = this; - - // allow multiple hashes to be passed on init - options = !isMethodCall && args.length ? - $.widget.extend.apply( null, [ options ].concat(args) ) : - options; - - if ( isMethodCall ) { - this.each(function() { - var methodValue, - instance = $.data( this, fullName ); - if ( !instance ) { - return $.error( "cannot call methods on " + name + " prior to initialization; " + - "attempted to call method '" + options + "'" ); - } - if ( !$.isFunction( instance[options] ) || options.charAt( 0 ) === "_" ) { - return $.error( "no such method '" + options + "' for " + name + " widget instance" ); - } - methodValue = instance[ options ].apply( instance, args ); - if ( methodValue !== instance && methodValue !== undefined ) { - returnValue = methodValue && methodValue.jquery ? - returnValue.pushStack( methodValue.get() ) : - methodValue; - return false; - } - }); - } else { - this.each(function() { - var instance = $.data( this, fullName ); - if ( instance ) { - instance.option( options || {} )._init(); - } else { - $.data( this, fullName, new object( options, this ) ); - } - }); - } - - return returnValue; - }; -}; - -$.Widget = function( /* options, element */ ) {}; -$.Widget._childConstructors = []; - -$.Widget.prototype = { - widgetName: "widget", - widgetEventPrefix: "", - defaultElement: "
", - options: { - disabled: false, - - // callbacks - create: null - }, - _createWidget: function( options, element ) { - element = $( element || this.defaultElement || this )[ 0 ]; - this.element = $( element ); - this.uuid = uuid++; - this.eventNamespace = "." + this.widgetName + this.uuid; - this.options = $.widget.extend( {}, - this.options, - this._getCreateOptions(), - options ); - - this.bindings = $(); - this.hoverable = $(); - this.focusable = $(); - - if ( element !== this ) { - // 1.9 BC for #7810 - // TODO remove dual storage - $.data( element, this.widgetName, this ); - $.data( element, this.widgetFullName, this ); - this._on( true, this.element, { - remove: function( event ) { - if ( event.target === element ) { - this.destroy(); - } - } - }); - this.document = $( element.style ? - // element within the document - element.ownerDocument : - // element is window or document - element.document || element ); - this.window = $( this.document[0].defaultView || this.document[0].parentWindow ); - } - - this._create(); - this._trigger( "create", null, this._getCreateEventData() ); - this._init(); - }, - _getCreateOptions: $.noop, - _getCreateEventData: $.noop, - _create: $.noop, - _init: $.noop, - - destroy: function() { - this._destroy(); - // we can probably remove the unbind calls in 2.0 - // all event bindings should go through this._on() - this.element - .unbind( this.eventNamespace ) - // 1.9 BC for #7810 - // TODO remove dual storage - .removeData( this.widgetName ) - .removeData( this.widgetFullName ) - // support: jquery <1.6.3 - // http://bugs.jquery.com/ticket/9413 - .removeData( $.camelCase( this.widgetFullName ) ); - this.widget() - .unbind( this.eventNamespace ) - .removeAttr( "aria-disabled" ) - .removeClass( - this.widgetFullName + "-disabled " + - "ui-state-disabled" ); - - // clean up events and states - this.bindings.unbind( this.eventNamespace ); - this.hoverable.removeClass( "ui-state-hover" ); - this.focusable.removeClass( "ui-state-focus" ); - }, - _destroy: $.noop, - - widget: function() { - return this.element; - }, - - option: function( key, value ) { - var options = key, - parts, - curOption, - i; - - if ( arguments.length === 0 ) { - // don't return a reference to the internal hash - return $.widget.extend( {}, this.options ); - } - - if ( typeof key === "string" ) { - // handle nested keys, e.g., "foo.bar" => { foo: { bar: ___ } } - options = {}; - parts = key.split( "." ); - key = parts.shift(); - if ( parts.length ) { - curOption = options[ key ] = $.widget.extend( {}, this.options[ key ] ); - for ( i = 0; i < parts.length - 1; i++ ) { - curOption[ parts[ i ] ] = curOption[ parts[ i ] ] || {}; - curOption = curOption[ parts[ i ] ]; - } - key = parts.pop(); - if ( value === undefined ) { - return curOption[ key ] === undefined ? null : curOption[ key ]; - } - curOption[ key ] = value; - } else { - if ( value === undefined ) { - return this.options[ key ] === undefined ? null : this.options[ key ]; - } - options[ key ] = value; - } - } - - this._setOptions( options ); - - return this; - }, - _setOptions: function( options ) { - var key; - - for ( key in options ) { - this._setOption( key, options[ key ] ); - } - - return this; - }, - _setOption: function( key, value ) { - this.options[ key ] = value; - - if ( key === "disabled" ) { - this.widget() - .toggleClass( this.widgetFullName + "-disabled ui-state-disabled", !!value ) - .attr( "aria-disabled", value ); - this.hoverable.removeClass( "ui-state-hover" ); - this.focusable.removeClass( "ui-state-focus" ); - } - - return this; - }, - - enable: function() { - return this._setOption( "disabled", false ); - }, - disable: function() { - return this._setOption( "disabled", true ); - }, - - _on: function( suppressDisabledCheck, element, handlers ) { - var delegateElement, - instance = this; - - // no suppressDisabledCheck flag, shuffle arguments - if ( typeof suppressDisabledCheck !== "boolean" ) { - handlers = element; - element = suppressDisabledCheck; - suppressDisabledCheck = false; - } - - // no element argument, shuffle and use this.element - if ( !handlers ) { - handlers = element; - element = this.element; - delegateElement = this.widget(); - } else { - // accept selectors, DOM elements - element = delegateElement = $( element ); - this.bindings = this.bindings.add( element ); - } - - $.each( handlers, function( event, handler ) { - function handlerProxy() { - // allow widgets to customize the disabled handling - // - disabled as an array instead of boolean - // - disabled class as method for disabling individual parts - if ( !suppressDisabledCheck && - ( instance.options.disabled === true || - $( this ).hasClass( "ui-state-disabled" ) ) ) { - return; - } - return ( typeof handler === "string" ? instance[ handler ] : handler ) - .apply( instance, arguments ); - } - - // copy the guid so direct unbinding works - if ( typeof handler !== "string" ) { - handlerProxy.guid = handler.guid = - handler.guid || handlerProxy.guid || $.guid++; - } - - var match = event.match( /^(\w+)\s*(.*)$/ ), - eventName = match[1] + instance.eventNamespace, - selector = match[2]; - if ( selector ) { - delegateElement.delegate( selector, eventName, handlerProxy ); - } else { - element.bind( eventName, handlerProxy ); - } - }); - }, - - _off: function( element, eventName ) { - eventName = (eventName || "").split( " " ).join( this.eventNamespace + " " ) + this.eventNamespace; - element.unbind( eventName ).undelegate( eventName ); - }, - - _delay: function( handler, delay ) { - function handlerProxy() { - return ( typeof handler === "string" ? instance[ handler ] : handler ) - .apply( instance, arguments ); - } - var instance = this; - return setTimeout( handlerProxy, delay || 0 ); - }, - - _hoverable: function( element ) { - this.hoverable = this.hoverable.add( element ); - this._on( element, { - mouseenter: function( event ) { - $( event.currentTarget ).addClass( "ui-state-hover" ); - }, - mouseleave: function( event ) { - $( event.currentTarget ).removeClass( "ui-state-hover" ); - } - }); - }, - - _focusable: function( element ) { - this.focusable = this.focusable.add( element ); - this._on( element, { - focusin: function( event ) { - $( event.currentTarget ).addClass( "ui-state-focus" ); - }, - focusout: function( event ) { - $( event.currentTarget ).removeClass( "ui-state-focus" ); - } - }); - }, - - _trigger: function( type, event, data ) { - var prop, orig, - callback = this.options[ type ]; - - data = data || {}; - event = $.Event( event ); - event.type = ( type === this.widgetEventPrefix ? - type : - this.widgetEventPrefix + type ).toLowerCase(); - // the original event may come from any element - // so we need to reset the target on the new event - event.target = this.element[ 0 ]; - - // copy original event properties over to the new event - orig = event.originalEvent; - if ( orig ) { - for ( prop in orig ) { - if ( !( prop in event ) ) { - event[ prop ] = orig[ prop ]; - } - } - } - - this.element.trigger( event, data ); - return !( $.isFunction( callback ) && - callback.apply( this.element[0], [ event ].concat( data ) ) === false || - event.isDefaultPrevented() ); - } -}; - -$.each( { show: "fadeIn", hide: "fadeOut" }, function( method, defaultEffect ) { - $.Widget.prototype[ "_" + method ] = function( element, options, callback ) { - if ( typeof options === "string" ) { - options = { effect: options }; - } - var hasOptions, - effectName = !options ? - method : - options === true || typeof options === "number" ? - defaultEffect : - options.effect || defaultEffect; - options = options || {}; - if ( typeof options === "number" ) { - options = { duration: options }; - } - hasOptions = !$.isEmptyObject( options ); - options.complete = callback; - if ( options.delay ) { - element.delay( options.delay ); - } - if ( hasOptions && $.effects && ( $.effects.effect[ effectName ] || $.uiBackCompat !== false && $.effects[ effectName ] ) ) { - element[ method ]( options ); - } else if ( effectName !== method && element[ effectName ] ) { - element[ effectName ]( options.duration, options.easing, callback ); - } else { - element.queue(function( next ) { - $( this )[ method ](); - if ( callback ) { - callback.call( element[ 0 ] ); - } - next(); - }); - } - }; -}); - -// DEPRECATED -if ( $.uiBackCompat !== false ) { - $.Widget.prototype._getCreateOptions = function() { - return $.metadata && $.metadata.get( this.element[0] )[ this.widgetName ]; - }; -} - -})( jQuery ); - -(function( $, undefined ) { - -var mouseHandled = false; -$( document ).mouseup( function( e ) { - mouseHandled = false; -}); - -$.widget("ui.mouse", { - version: "1.9.2", - options: { - cancel: 'input,textarea,button,select,option', - distance: 1, - delay: 0 - }, - _mouseInit: function() { - var that = this; - - this.element - .bind('mousedown.'+this.widgetName, function(event) { - return that._mouseDown(event); - }) - .bind('click.'+this.widgetName, function(event) { - if (true === $.data(event.target, that.widgetName + '.preventClickEvent')) { - $.removeData(event.target, that.widgetName + '.preventClickEvent'); - event.stopImmediatePropagation(); - return false; - } - }); - - this.started = false; - }, - - // TODO: make sure destroying one instance of mouse doesn't mess with - // other instances of mouse - _mouseDestroy: function() { - this.element.unbind('.'+this.widgetName); - if ( this._mouseMoveDelegate ) { - $(document) - .unbind('mousemove.'+this.widgetName, this._mouseMoveDelegate) - .unbind('mouseup.'+this.widgetName, this._mouseUpDelegate); - } - }, - - _mouseDown: function(event) { - // don't let more than one widget handle mouseStart - if( mouseHandled ) { return; } - - // we may have missed mouseup (out of window) - (this._mouseStarted && this._mouseUp(event)); - - this._mouseDownEvent = event; - - var that = this, - btnIsLeft = (event.which === 1), - // event.target.nodeName works around a bug in IE 8 with - // disabled inputs (#7620) - elIsCancel = (typeof this.options.cancel === "string" && event.target.nodeName ? $(event.target).closest(this.options.cancel).length : false); - if (!btnIsLeft || elIsCancel || !this._mouseCapture(event)) { - return true; - } - - this.mouseDelayMet = !this.options.delay; - if (!this.mouseDelayMet) { - this._mouseDelayTimer = setTimeout(function() { - that.mouseDelayMet = true; - }, this.options.delay); - } - - if (this._mouseDistanceMet(event) && this._mouseDelayMet(event)) { - this._mouseStarted = (this._mouseStart(event) !== false); - if (!this._mouseStarted) { - event.preventDefault(); - return true; - } - } - - // Click event may never have fired (Gecko & Opera) - if (true === $.data(event.target, this.widgetName + '.preventClickEvent')) { - $.removeData(event.target, this.widgetName + '.preventClickEvent'); - } - - // these delegates are required to keep context - this._mouseMoveDelegate = function(event) { - return that._mouseMove(event); - }; - this._mouseUpDelegate = function(event) { - return that._mouseUp(event); - }; - $(document) - .bind('mousemove.'+this.widgetName, this._mouseMoveDelegate) - .bind('mouseup.'+this.widgetName, this._mouseUpDelegate); - - event.preventDefault(); - - mouseHandled = true; - return true; - }, - - _mouseMove: function(event) { - // IE mouseup check - mouseup happened when mouse was out of window - if ($.ui.ie && !(document.documentMode >= 9) && !event.button) { - return this._mouseUp(event); - } - - if (this._mouseStarted) { - this._mouseDrag(event); - return event.preventDefault(); - } - - if (this._mouseDistanceMet(event) && this._mouseDelayMet(event)) { - this._mouseStarted = - (this._mouseStart(this._mouseDownEvent, event) !== false); - (this._mouseStarted ? this._mouseDrag(event) : this._mouseUp(event)); - } - - return !this._mouseStarted; - }, - - _mouseUp: function(event) { - $(document) - .unbind('mousemove.'+this.widgetName, this._mouseMoveDelegate) - .unbind('mouseup.'+this.widgetName, this._mouseUpDelegate); - - if (this._mouseStarted) { - this._mouseStarted = false; - - if (event.target === this._mouseDownEvent.target) { - $.data(event.target, this.widgetName + '.preventClickEvent', true); - } - - this._mouseStop(event); - } - - return false; - }, - - _mouseDistanceMet: function(event) { - return (Math.max( - Math.abs(this._mouseDownEvent.pageX - event.pageX), - Math.abs(this._mouseDownEvent.pageY - event.pageY) - ) >= this.options.distance - ); - }, - - _mouseDelayMet: function(event) { - return this.mouseDelayMet; - }, - - // These are placeholder methods, to be overriden by extending plugin - _mouseStart: function(event) {}, - _mouseDrag: function(event) {}, - _mouseStop: function(event) {}, - _mouseCapture: function(event) { return true; } -}); - -})(jQuery); - -(function( $, undefined ) { - -$.widget("ui.draggable", $.ui.mouse, { - version: "1.9.2", - widgetEventPrefix: "drag", - options: { - addClasses: true, - appendTo: "parent", - axis: false, - connectToSortable: false, - containment: false, - cursor: "auto", - cursorAt: false, - grid: false, - handle: false, - helper: "original", - iframeFix: false, - opacity: false, - refreshPositions: false, - revert: false, - revertDuration: 500, - scope: "default", - scroll: true, - scrollSensitivity: 20, - scrollSpeed: 20, - snap: false, - snapMode: "both", - snapTolerance: 20, - stack: false, - zIndex: false - }, - _create: function() { - - if (this.options.helper == 'original' && !(/^(?:r|a|f)/).test(this.element.css("position"))) - this.element[0].style.position = 'relative'; - - (this.options.addClasses && this.element.addClass("ui-draggable")); - (this.options.disabled && this.element.addClass("ui-draggable-disabled")); - - this._mouseInit(); - - }, - - _destroy: function() { - this.element.removeClass( "ui-draggable ui-draggable-dragging ui-draggable-disabled" ); - this._mouseDestroy(); - }, - - _mouseCapture: function(event) { - - var o = this.options; - - // among others, prevent a drag on a resizable-handle - if (this.helper || o.disabled || $(event.target).is('.ui-resizable-handle')) - return false; - - //Quit if we're not on a valid handle - this.handle = this._getHandle(event); - if (!this.handle) - return false; - - $(o.iframeFix === true ? "iframe" : o.iframeFix).each(function() { - $('
') - .css({ - width: this.offsetWidth+"px", height: this.offsetHeight+"px", - position: "absolute", opacity: "0.001", zIndex: 1000 - }) - .css($(this).offset()) - .appendTo("body"); - }); - - return true; - - }, - - _mouseStart: function(event) { - - var o = this.options; - - //Create and append the visible helper - this.helper = this._createHelper(event); - - this.helper.addClass("ui-draggable-dragging"); - - //Cache the helper size - this._cacheHelperProportions(); - - //If ddmanager is used for droppables, set the global draggable - if($.ui.ddmanager) - $.ui.ddmanager.current = this; - - /* - * - Position generation - - * This block generates everything position related - it's the core of draggables. - */ - - //Cache the margins of the original element - this._cacheMargins(); - - //Store the helper's css position - this.cssPosition = this.helper.css("position"); - this.scrollParent = this.helper.scrollParent(); - - //The element's absolute position on the page minus margins - this.offset = this.positionAbs = this.element.offset(); - this.offset = { - top: this.offset.top - this.margins.top, - left: this.offset.left - this.margins.left - }; - - $.extend(this.offset, { - click: { //Where the click happened, relative to the element - left: event.pageX - this.offset.left, - top: event.pageY - this.offset.top - }, - parent: this._getParentOffset(), - relative: this._getRelativeOffset() //This is a relative to absolute position minus the actual position calculation - only used for relative positioned helper - }); - - //Generate the original position - this.originalPosition = this.position = this._generatePosition(event); - this.originalPageX = event.pageX; - this.originalPageY = event.pageY; - - //Adjust the mouse offset relative to the helper if 'cursorAt' is supplied - (o.cursorAt && this._adjustOffsetFromHelper(o.cursorAt)); - - //Set a containment if given in the options - if(o.containment) - this._setContainment(); - - //Trigger event + callbacks - if(this._trigger("start", event) === false) { - this._clear(); - return false; - } - - //Recache the helper size - this._cacheHelperProportions(); - - //Prepare the droppable offsets - if ($.ui.ddmanager && !o.dropBehaviour) - $.ui.ddmanager.prepareOffsets(this, event); - - - this._mouseDrag(event, true); //Execute the drag once - this causes the helper not to be visible before getting its correct position - - //If the ddmanager is used for droppables, inform the manager that dragging has started (see #5003) - if ( $.ui.ddmanager ) $.ui.ddmanager.dragStart(this, event); - - return true; - }, - - _mouseDrag: function(event, noPropagation) { - - //Compute the helpers position - this.position = this._generatePosition(event); - this.positionAbs = this._convertPositionTo("absolute"); - - //Call plugins and callbacks and use the resulting position if something is returned - if (!noPropagation) { - var ui = this._uiHash(); - if(this._trigger('drag', event, ui) === false) { - this._mouseUp({}); - return false; - } - this.position = ui.position; - } - - if(!this.options.axis || this.options.axis != "y") this.helper[0].style.left = this.position.left+'px'; - if(!this.options.axis || this.options.axis != "x") this.helper[0].style.top = this.position.top+'px'; - if($.ui.ddmanager) $.ui.ddmanager.drag(this, event); - - return false; - }, - - _mouseStop: function(event) { - - //If we are using droppables, inform the manager about the drop - var dropped = false; - if ($.ui.ddmanager && !this.options.dropBehaviour) - dropped = $.ui.ddmanager.drop(this, event); - - //if a drop comes from outside (a sortable) - if(this.dropped) { - dropped = this.dropped; - this.dropped = false; - } - - //if the original element is no longer in the DOM don't bother to continue (see #8269) - var element = this.element[0], elementInDom = false; - while ( element && (element = element.parentNode) ) { - if (element == document ) { - elementInDom = true; - } - } - if ( !elementInDom && this.options.helper === "original" ) - return false; - - if((this.options.revert == "invalid" && !dropped) || (this.options.revert == "valid" && dropped) || this.options.revert === true || ($.isFunction(this.options.revert) && this.options.revert.call(this.element, dropped))) { - var that = this; - $(this.helper).animate(this.originalPosition, parseInt(this.options.revertDuration, 10), function() { - if(that._trigger("stop", event) !== false) { - that._clear(); - } - }); - } else { - if(this._trigger("stop", event) !== false) { - this._clear(); - } - } - - return false; - }, - - _mouseUp: function(event) { - //Remove frame helpers - $("div.ui-draggable-iframeFix").each(function() { - this.parentNode.removeChild(this); - }); - - //If the ddmanager is used for droppables, inform the manager that dragging has stopped (see #5003) - if( $.ui.ddmanager ) $.ui.ddmanager.dragStop(this, event); - - return $.ui.mouse.prototype._mouseUp.call(this, event); - }, - - cancel: function() { - - if(this.helper.is(".ui-draggable-dragging")) { - this._mouseUp({}); - } else { - this._clear(); - } - - return this; - - }, - - _getHandle: function(event) { - - var handle = !this.options.handle || !$(this.options.handle, this.element).length ? true : false; - $(this.options.handle, this.element) - .find("*") - .andSelf() - .each(function() { - if(this == event.target) handle = true; - }); - - return handle; - - }, - - _createHelper: function(event) { - - var o = this.options; - var helper = $.isFunction(o.helper) ? $(o.helper.apply(this.element[0], [event])) : (o.helper == 'clone' ? this.element.clone().removeAttr('id') : this.element); - - if(!helper.parents('body').length) - helper.appendTo((o.appendTo == 'parent' ? this.element[0].parentNode : o.appendTo)); - - if(helper[0] != this.element[0] && !(/(fixed|absolute)/).test(helper.css("position"))) - helper.css("position", "absolute"); - - return helper; - - }, - - _adjustOffsetFromHelper: function(obj) { - if (typeof obj == 'string') { - obj = obj.split(' '); - } - if ($.isArray(obj)) { - obj = {left: +obj[0], top: +obj[1] || 0}; - } - if ('left' in obj) { - this.offset.click.left = obj.left + this.margins.left; - } - if ('right' in obj) { - this.offset.click.left = this.helperProportions.width - obj.right + this.margins.left; - } - if ('top' in obj) { - this.offset.click.top = obj.top + this.margins.top; - } - if ('bottom' in obj) { - this.offset.click.top = this.helperProportions.height - obj.bottom + this.margins.top; - } - }, - - _getParentOffset: function() { - - //Get the offsetParent and cache its position - this.offsetParent = this.helper.offsetParent(); - var po = this.offsetParent.offset(); - - // This is a special case where we need to modify a offset calculated on start, since the following happened: - // 1. The position of the helper is absolute, so it's position is calculated based on the next positioned parent - // 2. The actual offset parent is a child of the scroll parent, and the scroll parent isn't the document, which means that - // the scroll is included in the initial calculation of the offset of the parent, and never recalculated upon drag - if(this.cssPosition == 'absolute' && this.scrollParent[0] != document && $.contains(this.scrollParent[0], this.offsetParent[0])) { - po.left += this.scrollParent.scrollLeft(); - po.top += this.scrollParent.scrollTop(); - } - - if((this.offsetParent[0] == document.body) //This needs to be actually done for all browsers, since pageX/pageY includes this information - || (this.offsetParent[0].tagName && this.offsetParent[0].tagName.toLowerCase() == 'html' && $.ui.ie)) //Ugly IE fix - po = { top: 0, left: 0 }; - - return { - top: po.top + (parseInt(this.offsetParent.css("borderTopWidth"),10) || 0), - left: po.left + (parseInt(this.offsetParent.css("borderLeftWidth"),10) || 0) - }; - - }, - - _getRelativeOffset: function() { - - if(this.cssPosition == "relative") { - var p = this.element.position(); - return { - top: p.top - (parseInt(this.helper.css("top"),10) || 0) + this.scrollParent.scrollTop(), - left: p.left - (parseInt(this.helper.css("left"),10) || 0) + this.scrollParent.scrollLeft() - }; - } else { - return { top: 0, left: 0 }; - } - - }, - - _cacheMargins: function() { - this.margins = { - left: (parseInt(this.element.css("marginLeft"),10) || 0), - top: (parseInt(this.element.css("marginTop"),10) || 0), - right: (parseInt(this.element.css("marginRight"),10) || 0), - bottom: (parseInt(this.element.css("marginBottom"),10) || 0) - }; - }, - - _cacheHelperProportions: function() { - this.helperProportions = { - width: this.helper.outerWidth(), - height: this.helper.outerHeight() - }; - }, - - _setContainment: function() { - - var o = this.options; - if(o.containment == 'parent') o.containment = this.helper[0].parentNode; - if(o.containment == 'document' || o.containment == 'window') this.containment = [ - o.containment == 'document' ? 0 : $(window).scrollLeft() - this.offset.relative.left - this.offset.parent.left, - o.containment == 'document' ? 0 : $(window).scrollTop() - this.offset.relative.top - this.offset.parent.top, - (o.containment == 'document' ? 0 : $(window).scrollLeft()) + $(o.containment == 'document' ? document : window).width() - this.helperProportions.width - this.margins.left, - (o.containment == 'document' ? 0 : $(window).scrollTop()) + ($(o.containment == 'document' ? document : window).height() || document.body.parentNode.scrollHeight) - this.helperProportions.height - this.margins.top - ]; - - if(!(/^(document|window|parent)$/).test(o.containment) && o.containment.constructor != Array) { - var c = $(o.containment); - var ce = c[0]; if(!ce) return; - var co = c.offset(); - var over = ($(ce).css("overflow") != 'hidden'); - - this.containment = [ - (parseInt($(ce).css("borderLeftWidth"),10) || 0) + (parseInt($(ce).css("paddingLeft"),10) || 0), - (parseInt($(ce).css("borderTopWidth"),10) || 0) + (parseInt($(ce).css("paddingTop"),10) || 0), - (over ? Math.max(ce.scrollWidth,ce.offsetWidth) : ce.offsetWidth) - (parseInt($(ce).css("borderLeftWidth"),10) || 0) - (parseInt($(ce).css("paddingRight"),10) || 0) - this.helperProportions.width - this.margins.left - this.margins.right, - (over ? Math.max(ce.scrollHeight,ce.offsetHeight) : ce.offsetHeight) - (parseInt($(ce).css("borderTopWidth"),10) || 0) - (parseInt($(ce).css("paddingBottom"),10) || 0) - this.helperProportions.height - this.margins.top - this.margins.bottom - ]; - this.relative_container = c; - - } else if(o.containment.constructor == Array) { - this.containment = o.containment; - } - - }, - - _convertPositionTo: function(d, pos) { - - if(!pos) pos = this.position; - var mod = d == "absolute" ? 1 : -1; - var o = this.options, scroll = this.cssPosition == 'absolute' && !(this.scrollParent[0] != document && $.contains(this.scrollParent[0], this.offsetParent[0])) ? this.offsetParent : this.scrollParent, scrollIsRootNode = (/(html|body)/i).test(scroll[0].tagName); - - return { - top: ( - pos.top // The absolute mouse position - + this.offset.relative.top * mod // Only for relative positioned nodes: Relative offset from element to offset parent - + this.offset.parent.top * mod // The offsetParent's offset without borders (offset + border) - - ( ( this.cssPosition == 'fixed' ? -this.scrollParent.scrollTop() : ( scrollIsRootNode ? 0 : scroll.scrollTop() ) ) * mod) - ), - left: ( - pos.left // The absolute mouse position - + this.offset.relative.left * mod // Only for relative positioned nodes: Relative offset from element to offset parent - + this.offset.parent.left * mod // The offsetParent's offset without borders (offset + border) - - ( ( this.cssPosition == 'fixed' ? -this.scrollParent.scrollLeft() : scrollIsRootNode ? 0 : scroll.scrollLeft() ) * mod) - ) - }; - - }, - - _generatePosition: function(event) { - - var o = this.options, scroll = this.cssPosition == 'absolute' && !(this.scrollParent[0] != document && $.contains(this.scrollParent[0], this.offsetParent[0])) ? this.offsetParent : this.scrollParent, scrollIsRootNode = (/(html|body)/i).test(scroll[0].tagName); - var pageX = event.pageX; - var pageY = event.pageY; - - /* - * - Position constraining - - * Constrain the position to a mix of grid, containment. - */ - - if(this.originalPosition) { //If we are not dragging yet, we won't check for options - var containment; - if(this.containment) { - if (this.relative_container){ - var co = this.relative_container.offset(); - containment = [ this.containment[0] + co.left, - this.containment[1] + co.top, - this.containment[2] + co.left, - this.containment[3] + co.top ]; - } - else { - containment = this.containment; - } - - if(event.pageX - this.offset.click.left < containment[0]) pageX = containment[0] + this.offset.click.left; - if(event.pageY - this.offset.click.top < containment[1]) pageY = containment[1] + this.offset.click.top; - if(event.pageX - this.offset.click.left > containment[2]) pageX = containment[2] + this.offset.click.left; - if(event.pageY - this.offset.click.top > containment[3]) pageY = containment[3] + this.offset.click.top; - } - - if(o.grid) { - //Check for grid elements set to 0 to prevent divide by 0 error causing invalid argument errors in IE (see ticket #6950) - var top = o.grid[1] ? this.originalPageY + Math.round((pageY - this.originalPageY) / o.grid[1]) * o.grid[1] : this.originalPageY; - pageY = containment ? (!(top - this.offset.click.top < containment[1] || top - this.offset.click.top > containment[3]) ? top : (!(top - this.offset.click.top < containment[1]) ? top - o.grid[1] : top + o.grid[1])) : top; - - var left = o.grid[0] ? this.originalPageX + Math.round((pageX - this.originalPageX) / o.grid[0]) * o.grid[0] : this.originalPageX; - pageX = containment ? (!(left - this.offset.click.left < containment[0] || left - this.offset.click.left > containment[2]) ? left : (!(left - this.offset.click.left < containment[0]) ? left - o.grid[0] : left + o.grid[0])) : left; - } - - } - - return { - top: ( - pageY // The absolute mouse position - - this.offset.click.top // Click offset (relative to the element) - - this.offset.relative.top // Only for relative positioned nodes: Relative offset from element to offset parent - - this.offset.parent.top // The offsetParent's offset without borders (offset + border) - + ( ( this.cssPosition == 'fixed' ? -this.scrollParent.scrollTop() : ( scrollIsRootNode ? 0 : scroll.scrollTop() ) )) - ), - left: ( - pageX // The absolute mouse position - - this.offset.click.left // Click offset (relative to the element) - - this.offset.relative.left // Only for relative positioned nodes: Relative offset from element to offset parent - - this.offset.parent.left // The offsetParent's offset without borders (offset + border) - + ( ( this.cssPosition == 'fixed' ? -this.scrollParent.scrollLeft() : scrollIsRootNode ? 0 : scroll.scrollLeft() )) - ) - }; - - }, - - _clear: function() { - this.helper.removeClass("ui-draggable-dragging"); - if(this.helper[0] != this.element[0] && !this.cancelHelperRemoval) this.helper.remove(); - //if($.ui.ddmanager) $.ui.ddmanager.current = null; - this.helper = null; - this.cancelHelperRemoval = false; - }, - - // From now on bulk stuff - mainly helpers - - _trigger: function(type, event, ui) { - ui = ui || this._uiHash(); - $.ui.plugin.call(this, type, [event, ui]); - if(type == "drag") this.positionAbs = this._convertPositionTo("absolute"); //The absolute position has to be recalculated after plugins - return $.Widget.prototype._trigger.call(this, type, event, ui); - }, - - plugins: {}, - - _uiHash: function(event) { - return { - helper: this.helper, - position: this.position, - originalPosition: this.originalPosition, - offset: this.positionAbs - }; - } - -}); - -$.ui.plugin.add("draggable", "connectToSortable", { - start: function(event, ui) { - - var inst = $(this).data("draggable"), o = inst.options, - uiSortable = $.extend({}, ui, { item: inst.element }); - inst.sortables = []; - $(o.connectToSortable).each(function() { - var sortable = $.data(this, 'sortable'); - if (sortable && !sortable.options.disabled) { - inst.sortables.push({ - instance: sortable, - shouldRevert: sortable.options.revert - }); - sortable.refreshPositions(); // Call the sortable's refreshPositions at drag start to refresh the containerCache since the sortable container cache is used in drag and needs to be up to date (this will ensure it's initialised as well as being kept in step with any changes that might have happened on the page). - sortable._trigger("activate", event, uiSortable); - } - }); - - }, - stop: function(event, ui) { - - //If we are still over the sortable, we fake the stop event of the sortable, but also remove helper - var inst = $(this).data("draggable"), - uiSortable = $.extend({}, ui, { item: inst.element }); - - $.each(inst.sortables, function() { - if(this.instance.isOver) { - - this.instance.isOver = 0; - - inst.cancelHelperRemoval = true; //Don't remove the helper in the draggable instance - this.instance.cancelHelperRemoval = false; //Remove it in the sortable instance (so sortable plugins like revert still work) - - //The sortable revert is supported, and we have to set a temporary dropped variable on the draggable to support revert: 'valid/invalid' - if(this.shouldRevert) this.instance.options.revert = true; - - //Trigger the stop of the sortable - this.instance._mouseStop(event); - - this.instance.options.helper = this.instance.options._helper; - - //If the helper has been the original item, restore properties in the sortable - if(inst.options.helper == 'original') - this.instance.currentItem.css({ top: 'auto', left: 'auto' }); - - } else { - this.instance.cancelHelperRemoval = false; //Remove the helper in the sortable instance - this.instance._trigger("deactivate", event, uiSortable); - } - - }); - - }, - drag: function(event, ui) { - - var inst = $(this).data("draggable"), that = this; - - var checkPos = function(o) { - var dyClick = this.offset.click.top, dxClick = this.offset.click.left; - var helperTop = this.positionAbs.top, helperLeft = this.positionAbs.left; - var itemHeight = o.height, itemWidth = o.width; - var itemTop = o.top, itemLeft = o.left; - - return $.ui.isOver(helperTop + dyClick, helperLeft + dxClick, itemTop, itemLeft, itemHeight, itemWidth); - }; - - $.each(inst.sortables, function(i) { - - var innermostIntersecting = false; - var thisSortable = this; - //Copy over some variables to allow calling the sortable's native _intersectsWith - this.instance.positionAbs = inst.positionAbs; - this.instance.helperProportions = inst.helperProportions; - this.instance.offset.click = inst.offset.click; - - if(this.instance._intersectsWith(this.instance.containerCache)) { - innermostIntersecting = true; - $.each(inst.sortables, function () { - this.instance.positionAbs = inst.positionAbs; - this.instance.helperProportions = inst.helperProportions; - this.instance.offset.click = inst.offset.click; - if (this != thisSortable - && this.instance._intersectsWith(this.instance.containerCache) - && $.ui.contains(thisSortable.instance.element[0], this.instance.element[0])) - innermostIntersecting = false; - return innermostIntersecting; - }); - } - - - if(innermostIntersecting) { - //If it intersects, we use a little isOver variable and set it once, so our move-in stuff gets fired only once - if(!this.instance.isOver) { - - this.instance.isOver = 1; - //Now we fake the start of dragging for the sortable instance, - //by cloning the list group item, appending it to the sortable and using it as inst.currentItem - //We can then fire the start event of the sortable with our passed browser event, and our own helper (so it doesn't create a new one) - this.instance.currentItem = $(that).clone().removeAttr('id').appendTo(this.instance.element).data("sortable-item", true); - this.instance.options._helper = this.instance.options.helper; //Store helper option to later restore it - this.instance.options.helper = function() { return ui.helper[0]; }; - - event.target = this.instance.currentItem[0]; - this.instance._mouseCapture(event, true); - this.instance._mouseStart(event, true, true); - - //Because the browser event is way off the new appended portlet, we modify a couple of variables to reflect the changes - this.instance.offset.click.top = inst.offset.click.top; - this.instance.offset.click.left = inst.offset.click.left; - this.instance.offset.parent.left -= inst.offset.parent.left - this.instance.offset.parent.left; - this.instance.offset.parent.top -= inst.offset.parent.top - this.instance.offset.parent.top; - - inst._trigger("toSortable", event); - inst.dropped = this.instance.element; //draggable revert needs that - //hack so receive/update callbacks work (mostly) - inst.currentItem = inst.element; - this.instance.fromOutside = inst; - - } - - //Provided we did all the previous steps, we can fire the drag event of the sortable on every draggable drag, when it intersects with the sortable - if(this.instance.currentItem) this.instance._mouseDrag(event); - - } else { - - //If it doesn't intersect with the sortable, and it intersected before, - //we fake the drag stop of the sortable, but make sure it doesn't remove the helper by using cancelHelperRemoval - if(this.instance.isOver) { - - this.instance.isOver = 0; - this.instance.cancelHelperRemoval = true; - - //Prevent reverting on this forced stop - this.instance.options.revert = false; - - // The out event needs to be triggered independently - this.instance._trigger('out', event, this.instance._uiHash(this.instance)); - - this.instance._mouseStop(event, true); - this.instance.options.helper = this.instance.options._helper; - - //Now we remove our currentItem, the list group clone again, and the placeholder, and animate the helper back to it's original size - this.instance.currentItem.remove(); - if(this.instance.placeholder) this.instance.placeholder.remove(); - - inst._trigger("fromSortable", event); - inst.dropped = false; //draggable revert needs that - } - - }; - - }); - - } -}); - -$.ui.plugin.add("draggable", "cursor", { - start: function(event, ui) { - var t = $('body'), o = $(this).data('draggable').options; - if (t.css("cursor")) o._cursor = t.css("cursor"); - t.css("cursor", o.cursor); - }, - stop: function(event, ui) { - var o = $(this).data('draggable').options; - if (o._cursor) $('body').css("cursor", o._cursor); - } -}); - -$.ui.plugin.add("draggable", "opacity", { - start: function(event, ui) { - var t = $(ui.helper), o = $(this).data('draggable').options; - if(t.css("opacity")) o._opacity = t.css("opacity"); - t.css('opacity', o.opacity); - }, - stop: function(event, ui) { - var o = $(this).data('draggable').options; - if(o._opacity) $(ui.helper).css('opacity', o._opacity); - } -}); - -$.ui.plugin.add("draggable", "scroll", { - start: function(event, ui) { - var i = $(this).data("draggable"); - if(i.scrollParent[0] != document && i.scrollParent[0].tagName != 'HTML') i.overflowOffset = i.scrollParent.offset(); - }, - drag: function(event, ui) { - - var i = $(this).data("draggable"), o = i.options, scrolled = false; - - if(i.scrollParent[0] != document && i.scrollParent[0].tagName != 'HTML') { - - if(!o.axis || o.axis != 'x') { - if((i.overflowOffset.top + i.scrollParent[0].offsetHeight) - event.pageY < o.scrollSensitivity) - i.scrollParent[0].scrollTop = scrolled = i.scrollParent[0].scrollTop + o.scrollSpeed; - else if(event.pageY - i.overflowOffset.top < o.scrollSensitivity) - i.scrollParent[0].scrollTop = scrolled = i.scrollParent[0].scrollTop - o.scrollSpeed; - } - - if(!o.axis || o.axis != 'y') { - if((i.overflowOffset.left + i.scrollParent[0].offsetWidth) - event.pageX < o.scrollSensitivity) - i.scrollParent[0].scrollLeft = scrolled = i.scrollParent[0].scrollLeft + o.scrollSpeed; - else if(event.pageX - i.overflowOffset.left < o.scrollSensitivity) - i.scrollParent[0].scrollLeft = scrolled = i.scrollParent[0].scrollLeft - o.scrollSpeed; - } - - } else { - - if(!o.axis || o.axis != 'x') { - if(event.pageY - $(document).scrollTop() < o.scrollSensitivity) - scrolled = $(document).scrollTop($(document).scrollTop() - o.scrollSpeed); - else if($(window).height() - (event.pageY - $(document).scrollTop()) < o.scrollSensitivity) - scrolled = $(document).scrollTop($(document).scrollTop() + o.scrollSpeed); - } - - if(!o.axis || o.axis != 'y') { - if(event.pageX - $(document).scrollLeft() < o.scrollSensitivity) - scrolled = $(document).scrollLeft($(document).scrollLeft() - o.scrollSpeed); - else if($(window).width() - (event.pageX - $(document).scrollLeft()) < o.scrollSensitivity) - scrolled = $(document).scrollLeft($(document).scrollLeft() + o.scrollSpeed); - } - - } - - if(scrolled !== false && $.ui.ddmanager && !o.dropBehaviour) - $.ui.ddmanager.prepareOffsets(i, event); - - } -}); - -$.ui.plugin.add("draggable", "snap", { - start: function(event, ui) { - - var i = $(this).data("draggable"), o = i.options; - i.snapElements = []; - - $(o.snap.constructor != String ? ( o.snap.items || ':data(draggable)' ) : o.snap).each(function() { - var $t = $(this); var $o = $t.offset(); - if(this != i.element[0]) i.snapElements.push({ - item: this, - width: $t.outerWidth(), height: $t.outerHeight(), - top: $o.top, left: $o.left - }); - }); - - }, - drag: function(event, ui) { - - var inst = $(this).data("draggable"), o = inst.options; - var d = o.snapTolerance; - - var x1 = ui.offset.left, x2 = x1 + inst.helperProportions.width, - y1 = ui.offset.top, y2 = y1 + inst.helperProportions.height; - - for (var i = inst.snapElements.length - 1; i >= 0; i--){ - - var l = inst.snapElements[i].left, r = l + inst.snapElements[i].width, - t = inst.snapElements[i].top, b = t + inst.snapElements[i].height; - - //Yes, I know, this is insane ;) - if(!((l-d < x1 && x1 < r+d && t-d < y1 && y1 < b+d) || (l-d < x1 && x1 < r+d && t-d < y2 && y2 < b+d) || (l-d < x2 && x2 < r+d && t-d < y1 && y1 < b+d) || (l-d < x2 && x2 < r+d && t-d < y2 && y2 < b+d))) { - if(inst.snapElements[i].snapping) (inst.options.snap.release && inst.options.snap.release.call(inst.element, event, $.extend(inst._uiHash(), { snapItem: inst.snapElements[i].item }))); - inst.snapElements[i].snapping = false; - continue; - } - - if(o.snapMode != 'inner') { - var ts = Math.abs(t - y2) <= d; - var bs = Math.abs(b - y1) <= d; - var ls = Math.abs(l - x2) <= d; - var rs = Math.abs(r - x1) <= d; - if(ts) ui.position.top = inst._convertPositionTo("relative", { top: t - inst.helperProportions.height, left: 0 }).top - inst.margins.top; - if(bs) ui.position.top = inst._convertPositionTo("relative", { top: b, left: 0 }).top - inst.margins.top; - if(ls) ui.position.left = inst._convertPositionTo("relative", { top: 0, left: l - inst.helperProportions.width }).left - inst.margins.left; - if(rs) ui.position.left = inst._convertPositionTo("relative", { top: 0, left: r }).left - inst.margins.left; - } - - var first = (ts || bs || ls || rs); - - if(o.snapMode != 'outer') { - var ts = Math.abs(t - y1) <= d; - var bs = Math.abs(b - y2) <= d; - var ls = Math.abs(l - x1) <= d; - var rs = Math.abs(r - x2) <= d; - if(ts) ui.position.top = inst._convertPositionTo("relative", { top: t, left: 0 }).top - inst.margins.top; - if(bs) ui.position.top = inst._convertPositionTo("relative", { top: b - inst.helperProportions.height, left: 0 }).top - inst.margins.top; - if(ls) ui.position.left = inst._convertPositionTo("relative", { top: 0, left: l }).left - inst.margins.left; - if(rs) ui.position.left = inst._convertPositionTo("relative", { top: 0, left: r - inst.helperProportions.width }).left - inst.margins.left; - } - - if(!inst.snapElements[i].snapping && (ts || bs || ls || rs || first)) - (inst.options.snap.snap && inst.options.snap.snap.call(inst.element, event, $.extend(inst._uiHash(), { snapItem: inst.snapElements[i].item }))); - inst.snapElements[i].snapping = (ts || bs || ls || rs || first); - - }; - - } -}); - -$.ui.plugin.add("draggable", "stack", { - start: function(event, ui) { - - var o = $(this).data("draggable").options; - - var group = $.makeArray($(o.stack)).sort(function(a,b) { - return (parseInt($(a).css("zIndex"),10) || 0) - (parseInt($(b).css("zIndex"),10) || 0); - }); - if (!group.length) { return; } - - var min = parseInt(group[0].style.zIndex) || 0; - $(group).each(function(i) { - this.style.zIndex = min + i; - }); - - this[0].style.zIndex = min + group.length; - - } -}); - -$.ui.plugin.add("draggable", "zIndex", { - start: function(event, ui) { - var t = $(ui.helper), o = $(this).data("draggable").options; - if(t.css("zIndex")) o._zIndex = t.css("zIndex"); - t.css('zIndex', o.zIndex); - }, - stop: function(event, ui) { - var o = $(this).data("draggable").options; - if(o._zIndex) $(ui.helper).css('zIndex', o._zIndex); - } -}); - -})(jQuery); - -(function( $, undefined ) { - -$.widget("ui.droppable", { - version: "1.9.2", - widgetEventPrefix: "drop", - options: { - accept: '*', - activeClass: false, - addClasses: true, - greedy: false, - hoverClass: false, - scope: 'default', - tolerance: 'intersect' - }, - _create: function() { - - var o = this.options, accept = o.accept; - this.isover = 0; this.isout = 1; - - this.accept = $.isFunction(accept) ? accept : function(d) { - return d.is(accept); - }; - - //Store the droppable's proportions - this.proportions = { width: this.element[0].offsetWidth, height: this.element[0].offsetHeight }; - - // Add the reference and positions to the manager - $.ui.ddmanager.droppables[o.scope] = $.ui.ddmanager.droppables[o.scope] || []; - $.ui.ddmanager.droppables[o.scope].push(this); - - (o.addClasses && this.element.addClass("ui-droppable")); - - }, - - _destroy: function() { - var drop = $.ui.ddmanager.droppables[this.options.scope]; - for ( var i = 0; i < drop.length; i++ ) - if ( drop[i] == this ) - drop.splice(i, 1); - - this.element.removeClass("ui-droppable ui-droppable-disabled"); - }, - - _setOption: function(key, value) { - - if(key == 'accept') { - this.accept = $.isFunction(value) ? value : function(d) { - return d.is(value); - }; - } - $.Widget.prototype._setOption.apply(this, arguments); - }, - - _activate: function(event) { - var draggable = $.ui.ddmanager.current; - if(this.options.activeClass) this.element.addClass(this.options.activeClass); - (draggable && this._trigger('activate', event, this.ui(draggable))); - }, - - _deactivate: function(event) { - var draggable = $.ui.ddmanager.current; - if(this.options.activeClass) this.element.removeClass(this.options.activeClass); - (draggable && this._trigger('deactivate', event, this.ui(draggable))); - }, - - _over: function(event) { - - var draggable = $.ui.ddmanager.current; - if (!draggable || (draggable.currentItem || draggable.element)[0] == this.element[0]) return; // Bail if draggable and droppable are same element - - if (this.accept.call(this.element[0],(draggable.currentItem || draggable.element))) { - if(this.options.hoverClass) this.element.addClass(this.options.hoverClass); - this._trigger('over', event, this.ui(draggable)); - } - - }, - - _out: function(event) { - - var draggable = $.ui.ddmanager.current; - if (!draggable || (draggable.currentItem || draggable.element)[0] == this.element[0]) return; // Bail if draggable and droppable are same element - - if (this.accept.call(this.element[0],(draggable.currentItem || draggable.element))) { - if(this.options.hoverClass) this.element.removeClass(this.options.hoverClass); - this._trigger('out', event, this.ui(draggable)); - } - - }, - - _drop: function(event,custom) { - - var draggable = custom || $.ui.ddmanager.current; - if (!draggable || (draggable.currentItem || draggable.element)[0] == this.element[0]) return false; // Bail if draggable and droppable are same element - - var childrenIntersection = false; - this.element.find(":data(droppable)").not(".ui-draggable-dragging").each(function() { - var inst = $.data(this, 'droppable'); - if( - inst.options.greedy - && !inst.options.disabled - && inst.options.scope == draggable.options.scope - && inst.accept.call(inst.element[0], (draggable.currentItem || draggable.element)) - && $.ui.intersect(draggable, $.extend(inst, { offset: inst.element.offset() }), inst.options.tolerance) - ) { childrenIntersection = true; return false; } - }); - if(childrenIntersection) return false; - - if(this.accept.call(this.element[0],(draggable.currentItem || draggable.element))) { - if(this.options.activeClass) this.element.removeClass(this.options.activeClass); - if(this.options.hoverClass) this.element.removeClass(this.options.hoverClass); - this._trigger('drop', event, this.ui(draggable)); - return this.element; - } - - return false; - - }, - - ui: function(c) { - return { - draggable: (c.currentItem || c.element), - helper: c.helper, - position: c.position, - offset: c.positionAbs - }; - } - -}); - -$.ui.intersect = function(draggable, droppable, toleranceMode) { - - if (!droppable.offset) return false; - - var x1 = (draggable.positionAbs || draggable.position.absolute).left, x2 = x1 + draggable.helperProportions.width, - y1 = (draggable.positionAbs || draggable.position.absolute).top, y2 = y1 + draggable.helperProportions.height; - var l = droppable.offset.left, r = l + droppable.proportions.width, - t = droppable.offset.top, b = t + droppable.proportions.height; - - switch (toleranceMode) { - case 'fit': - return (l <= x1 && x2 <= r - && t <= y1 && y2 <= b); - break; - case 'intersect': - return (l < x1 + (draggable.helperProportions.width / 2) // Right Half - && x2 - (draggable.helperProportions.width / 2) < r // Left Half - && t < y1 + (draggable.helperProportions.height / 2) // Bottom Half - && y2 - (draggable.helperProportions.height / 2) < b ); // Top Half - break; - case 'pointer': - var draggableLeft = ((draggable.positionAbs || draggable.position.absolute).left + (draggable.clickOffset || draggable.offset.click).left), - draggableTop = ((draggable.positionAbs || draggable.position.absolute).top + (draggable.clickOffset || draggable.offset.click).top), - isOver = $.ui.isOver(draggableTop, draggableLeft, t, l, droppable.proportions.height, droppable.proportions.width); - return isOver; - break; - case 'touch': - return ( - (y1 >= t && y1 <= b) || // Top edge touching - (y2 >= t && y2 <= b) || // Bottom edge touching - (y1 < t && y2 > b) // Surrounded vertically - ) && ( - (x1 >= l && x1 <= r) || // Left edge touching - (x2 >= l && x2 <= r) || // Right edge touching - (x1 < l && x2 > r) // Surrounded horizontally - ); - break; - default: - return false; - break; - } - -}; - -/* - This manager tracks offsets of draggables and droppables -*/ -$.ui.ddmanager = { - current: null, - droppables: { 'default': [] }, - prepareOffsets: function(t, event) { - - var m = $.ui.ddmanager.droppables[t.options.scope] || []; - var type = event ? event.type : null; // workaround for #2317 - var list = (t.currentItem || t.element).find(":data(droppable)").andSelf(); - - droppablesLoop: for (var i = 0; i < m.length; i++) { - - if(m[i].options.disabled || (t && !m[i].accept.call(m[i].element[0],(t.currentItem || t.element)))) continue; //No disabled and non-accepted - for (var j=0; j < list.length; j++) { if(list[j] == m[i].element[0]) { m[i].proportions.height = 0; continue droppablesLoop; } }; //Filter out elements in the current dragged item - m[i].visible = m[i].element.css("display") != "none"; if(!m[i].visible) continue; //If the element is not visible, continue - - if(type == "mousedown") m[i]._activate.call(m[i], event); //Activate the droppable if used directly from draggables - - m[i].offset = m[i].element.offset(); - m[i].proportions = { width: m[i].element[0].offsetWidth, height: m[i].element[0].offsetHeight }; - - } - - }, - drop: function(draggable, event) { - - var dropped = false; - $.each($.ui.ddmanager.droppables[draggable.options.scope] || [], function() { - - if(!this.options) return; - if (!this.options.disabled && this.visible && $.ui.intersect(draggable, this, this.options.tolerance)) - dropped = this._drop.call(this, event) || dropped; - - if (!this.options.disabled && this.visible && this.accept.call(this.element[0],(draggable.currentItem || draggable.element))) { - this.isout = 1; this.isover = 0; - this._deactivate.call(this, event); - } - - }); - return dropped; - - }, - dragStart: function( draggable, event ) { - //Listen for scrolling so that if the dragging causes scrolling the position of the droppables can be recalculated (see #5003) - draggable.element.parentsUntil( "body" ).bind( "scroll.droppable", function() { - if( !draggable.options.refreshPositions ) $.ui.ddmanager.prepareOffsets( draggable, event ); - }); - }, - drag: function(draggable, event) { - - //If you have a highly dynamic page, you might try this option. It renders positions every time you move the mouse. - if(draggable.options.refreshPositions) $.ui.ddmanager.prepareOffsets(draggable, event); - - //Run through all droppables and check their positions based on specific tolerance options - $.each($.ui.ddmanager.droppables[draggable.options.scope] || [], function() { - - if(this.options.disabled || this.greedyChild || !this.visible) return; - var intersects = $.ui.intersect(draggable, this, this.options.tolerance); - - var c = !intersects && this.isover == 1 ? 'isout' : (intersects && this.isover == 0 ? 'isover' : null); - if(!c) return; - - var parentInstance; - if (this.options.greedy) { - // find droppable parents with same scope - var scope = this.options.scope; - var parent = this.element.parents(':data(droppable)').filter(function () { - return $.data(this, 'droppable').options.scope === scope; - }); - - if (parent.length) { - parentInstance = $.data(parent[0], 'droppable'); - parentInstance.greedyChild = (c == 'isover' ? 1 : 0); - } - } - - // we just moved into a greedy child - if (parentInstance && c == 'isover') { - parentInstance['isover'] = 0; - parentInstance['isout'] = 1; - parentInstance._out.call(parentInstance, event); - } - - this[c] = 1; this[c == 'isout' ? 'isover' : 'isout'] = 0; - this[c == "isover" ? "_over" : "_out"].call(this, event); - - // we just moved out of a greedy child - if (parentInstance && c == 'isout') { - parentInstance['isout'] = 0; - parentInstance['isover'] = 1; - parentInstance._over.call(parentInstance, event); - } - }); - - }, - dragStop: function( draggable, event ) { - draggable.element.parentsUntil( "body" ).unbind( "scroll.droppable" ); - //Call prepareOffsets one final time since IE does not fire return scroll events when overflow was caused by drag (see #5003) - if( !draggable.options.refreshPositions ) $.ui.ddmanager.prepareOffsets( draggable, event ); - } -}; - -})(jQuery); - -(function( $, undefined ) { - -$.widget("ui.resizable", $.ui.mouse, { - version: "1.9.2", - widgetEventPrefix: "resize", - options: { - alsoResize: false, - animate: false, - animateDuration: "slow", - animateEasing: "swing", - aspectRatio: false, - autoHide: false, - containment: false, - ghost: false, - grid: false, - handles: "e,s,se", - helper: false, - maxHeight: null, - maxWidth: null, - minHeight: 10, - minWidth: 10, - zIndex: 1000 - }, - _create: function() { - - var that = this, o = this.options; - this.element.addClass("ui-resizable"); - - $.extend(this, { - _aspectRatio: !!(o.aspectRatio), - aspectRatio: o.aspectRatio, - originalElement: this.element, - _proportionallyResizeElements: [], - _helper: o.helper || o.ghost || o.animate ? o.helper || 'ui-resizable-helper' : null - }); - - //Wrap the element if it cannot hold child nodes - if(this.element[0].nodeName.match(/canvas|textarea|input|select|button|img/i)) { - - //Create a wrapper element and set the wrapper to the new current internal element - this.element.wrap( - $('
').css({ - position: this.element.css('position'), - width: this.element.outerWidth(), - height: this.element.outerHeight(), - top: this.element.css('top'), - left: this.element.css('left') - }) - ); - - //Overwrite the original this.element - this.element = this.element.parent().data( - "resizable", this.element.data('resizable') - ); - - this.elementIsWrapper = true; - - //Move margins to the wrapper - this.element.css({ marginLeft: this.originalElement.css("marginLeft"), marginTop: this.originalElement.css("marginTop"), marginRight: this.originalElement.css("marginRight"), marginBottom: this.originalElement.css("marginBottom") }); - this.originalElement.css({ marginLeft: 0, marginTop: 0, marginRight: 0, marginBottom: 0}); - - //Prevent Safari textarea resize - this.originalResizeStyle = this.originalElement.css('resize'); - this.originalElement.css('resize', 'none'); - - //Push the actual element to our proportionallyResize internal array - this._proportionallyResizeElements.push(this.originalElement.css({ position: 'static', zoom: 1, display: 'block' })); - - // avoid IE jump (hard set the margin) - this.originalElement.css({ margin: this.originalElement.css('margin') }); - - // fix handlers offset - this._proportionallyResize(); - - } - - this.handles = o.handles || (!$('.ui-resizable-handle', this.element).length ? "e,s,se" : { n: '.ui-resizable-n', e: '.ui-resizable-e', s: '.ui-resizable-s', w: '.ui-resizable-w', se: '.ui-resizable-se', sw: '.ui-resizable-sw', ne: '.ui-resizable-ne', nw: '.ui-resizable-nw' }); - if(this.handles.constructor == String) { - - if(this.handles == 'all') this.handles = 'n,e,s,w,se,sw,ne,nw'; - var n = this.handles.split(","); this.handles = {}; - - for(var i = 0; i < n.length; i++) { - - var handle = $.trim(n[i]), hname = 'ui-resizable-'+handle; - var axis = $('
'); - - // Apply zIndex to all handles - see #7960 - axis.css({ zIndex: o.zIndex }); - - //TODO : What's going on here? - if ('se' == handle) { - axis.addClass('ui-icon ui-icon-gripsmall-diagonal-se'); - }; - - //Insert into internal handles object and append to element - this.handles[handle] = '.ui-resizable-'+handle; - this.element.append(axis); - } - - } - - this._renderAxis = function(target) { - - target = target || this.element; - - for(var i in this.handles) { - - if(this.handles[i].constructor == String) - this.handles[i] = $(this.handles[i], this.element).show(); - - //Apply pad to wrapper element, needed to fix axis position (textarea, inputs, scrolls) - if (this.elementIsWrapper && this.originalElement[0].nodeName.match(/textarea|input|select|button/i)) { - - var axis = $(this.handles[i], this.element), padWrapper = 0; - - //Checking the correct pad and border - padWrapper = /sw|ne|nw|se|n|s/.test(i) ? axis.outerHeight() : axis.outerWidth(); - - //The padding type i have to apply... - var padPos = [ 'padding', - /ne|nw|n/.test(i) ? 'Top' : - /se|sw|s/.test(i) ? 'Bottom' : - /^e$/.test(i) ? 'Right' : 'Left' ].join(""); - - target.css(padPos, padWrapper); - - this._proportionallyResize(); - - } - - //TODO: What's that good for? There's not anything to be executed left - if(!$(this.handles[i]).length) - continue; - - } - }; - - //TODO: make renderAxis a prototype function - this._renderAxis(this.element); - - this._handles = $('.ui-resizable-handle', this.element) - .disableSelection(); - - //Matching axis name - this._handles.mouseover(function() { - if (!that.resizing) { - if (this.className) - var axis = this.className.match(/ui-resizable-(se|sw|ne|nw|n|e|s|w)/i); - //Axis, default = se - that.axis = axis && axis[1] ? axis[1] : 'se'; - } - }); - - //If we want to auto hide the elements - if (o.autoHide) { - this._handles.hide(); - $(this.element) - .addClass("ui-resizable-autohide") - .mouseenter(function() { - if (o.disabled) return; - $(this).removeClass("ui-resizable-autohide"); - that._handles.show(); - }) - .mouseleave(function(){ - if (o.disabled) return; - if (!that.resizing) { - $(this).addClass("ui-resizable-autohide"); - that._handles.hide(); - } - }); - } - - //Initialize the mouse interaction - this._mouseInit(); - - }, - - _destroy: function() { - - this._mouseDestroy(); - - var _destroy = function(exp) { - $(exp).removeClass("ui-resizable ui-resizable-disabled ui-resizable-resizing") - .removeData("resizable").removeData("ui-resizable").unbind(".resizable").find('.ui-resizable-handle').remove(); - }; - - //TODO: Unwrap at same DOM position - if (this.elementIsWrapper) { - _destroy(this.element); - var wrapper = this.element; - this.originalElement.css({ - position: wrapper.css('position'), - width: wrapper.outerWidth(), - height: wrapper.outerHeight(), - top: wrapper.css('top'), - left: wrapper.css('left') - }).insertAfter( wrapper ); - wrapper.remove(); - } - - this.originalElement.css('resize', this.originalResizeStyle); - _destroy(this.originalElement); - - return this; - }, - - _mouseCapture: function(event) { - var handle = false; - for (var i in this.handles) { - if ($(this.handles[i])[0] == event.target) { - handle = true; - } - } - - return !this.options.disabled && handle; - }, - - _mouseStart: function(event) { - - var o = this.options, iniPos = this.element.position(), el = this.element; - - this.resizing = true; - this.documentScroll = { top: $(document).scrollTop(), left: $(document).scrollLeft() }; - - // bugfix for http://dev.jquery.com/ticket/1749 - if (el.is('.ui-draggable') || (/absolute/).test(el.css('position'))) { - el.css({ position: 'absolute', top: iniPos.top, left: iniPos.left }); - } - - this._renderProxy(); - - var curleft = num(this.helper.css('left')), curtop = num(this.helper.css('top')); - - if (o.containment) { - curleft += $(o.containment).scrollLeft() || 0; - curtop += $(o.containment).scrollTop() || 0; - } - - //Store needed variables - this.offset = this.helper.offset(); - this.position = { left: curleft, top: curtop }; - this.size = this._helper ? { width: el.outerWidth(), height: el.outerHeight() } : { width: el.width(), height: el.height() }; - this.originalSize = this._helper ? { width: el.outerWidth(), height: el.outerHeight() } : { width: el.width(), height: el.height() }; - this.originalPosition = { left: curleft, top: curtop }; - this.sizeDiff = { width: el.outerWidth() - el.width(), height: el.outerHeight() - el.height() }; - this.originalMousePosition = { left: event.pageX, top: event.pageY }; - - //Aspect Ratio - this.aspectRatio = (typeof o.aspectRatio == 'number') ? o.aspectRatio : ((this.originalSize.width / this.originalSize.height) || 1); - - var cursor = $('.ui-resizable-' + this.axis).css('cursor'); - $('body').css('cursor', cursor == 'auto' ? this.axis + '-resize' : cursor); - - el.addClass("ui-resizable-resizing"); - this._propagate("start", event); - return true; - }, - - _mouseDrag: function(event) { - - //Increase performance, avoid regex - var el = this.helper, o = this.options, props = {}, - that = this, smp = this.originalMousePosition, a = this.axis; - - var dx = (event.pageX-smp.left)||0, dy = (event.pageY-smp.top)||0; - var trigger = this._change[a]; - if (!trigger) return false; - - // Calculate the attrs that will be change - var data = trigger.apply(this, [event, dx, dy]); - - // Put this in the mouseDrag handler since the user can start pressing shift while resizing - this._updateVirtualBoundaries(event.shiftKey); - if (this._aspectRatio || event.shiftKey) - data = this._updateRatio(data, event); - - data = this._respectSize(data, event); - - // plugins callbacks need to be called first - this._propagate("resize", event); - - el.css({ - top: this.position.top + "px", left: this.position.left + "px", - width: this.size.width + "px", height: this.size.height + "px" - }); - - if (!this._helper && this._proportionallyResizeElements.length) - this._proportionallyResize(); - - this._updateCache(data); - - // calling the user callback at the end - this._trigger('resize', event, this.ui()); - - return false; - }, - - _mouseStop: function(event) { - - this.resizing = false; - var o = this.options, that = this; - - if(this._helper) { - var pr = this._proportionallyResizeElements, ista = pr.length && (/textarea/i).test(pr[0].nodeName), - soffseth = ista && $.ui.hasScroll(pr[0], 'left') /* TODO - jump height */ ? 0 : that.sizeDiff.height, - soffsetw = ista ? 0 : that.sizeDiff.width; - - var s = { width: (that.helper.width() - soffsetw), height: (that.helper.height() - soffseth) }, - left = (parseInt(that.element.css('left'), 10) + (that.position.left - that.originalPosition.left)) || null, - top = (parseInt(that.element.css('top'), 10) + (that.position.top - that.originalPosition.top)) || null; - - if (!o.animate) - this.element.css($.extend(s, { top: top, left: left })); - - that.helper.height(that.size.height); - that.helper.width(that.size.width); - - if (this._helper && !o.animate) this._proportionallyResize(); - } - - $('body').css('cursor', 'auto'); - - this.element.removeClass("ui-resizable-resizing"); - - this._propagate("stop", event); - - if (this._helper) this.helper.remove(); - return false; - - }, - - _updateVirtualBoundaries: function(forceAspectRatio) { - var o = this.options, pMinWidth, pMaxWidth, pMinHeight, pMaxHeight, b; - - b = { - minWidth: isNumber(o.minWidth) ? o.minWidth : 0, - maxWidth: isNumber(o.maxWidth) ? o.maxWidth : Infinity, - minHeight: isNumber(o.minHeight) ? o.minHeight : 0, - maxHeight: isNumber(o.maxHeight) ? o.maxHeight : Infinity - }; - - if(this._aspectRatio || forceAspectRatio) { - // We want to create an enclosing box whose aspect ration is the requested one - // First, compute the "projected" size for each dimension based on the aspect ratio and other dimension - pMinWidth = b.minHeight * this.aspectRatio; - pMinHeight = b.minWidth / this.aspectRatio; - pMaxWidth = b.maxHeight * this.aspectRatio; - pMaxHeight = b.maxWidth / this.aspectRatio; - - if(pMinWidth > b.minWidth) b.minWidth = pMinWidth; - if(pMinHeight > b.minHeight) b.minHeight = pMinHeight; - if(pMaxWidth < b.maxWidth) b.maxWidth = pMaxWidth; - if(pMaxHeight < b.maxHeight) b.maxHeight = pMaxHeight; - } - this._vBoundaries = b; - }, - - _updateCache: function(data) { - var o = this.options; - this.offset = this.helper.offset(); - if (isNumber(data.left)) this.position.left = data.left; - if (isNumber(data.top)) this.position.top = data.top; - if (isNumber(data.height)) this.size.height = data.height; - if (isNumber(data.width)) this.size.width = data.width; - }, - - _updateRatio: function(data, event) { - - var o = this.options, cpos = this.position, csize = this.size, a = this.axis; - - if (isNumber(data.height)) data.width = (data.height * this.aspectRatio); - else if (isNumber(data.width)) data.height = (data.width / this.aspectRatio); - - if (a == 'sw') { - data.left = cpos.left + (csize.width - data.width); - data.top = null; - } - if (a == 'nw') { - data.top = cpos.top + (csize.height - data.height); - data.left = cpos.left + (csize.width - data.width); - } - - return data; - }, - - _respectSize: function(data, event) { - - var el = this.helper, o = this._vBoundaries, pRatio = this._aspectRatio || event.shiftKey, a = this.axis, - ismaxw = isNumber(data.width) && o.maxWidth && (o.maxWidth < data.width), ismaxh = isNumber(data.height) && o.maxHeight && (o.maxHeight < data.height), - isminw = isNumber(data.width) && o.minWidth && (o.minWidth > data.width), isminh = isNumber(data.height) && o.minHeight && (o.minHeight > data.height); - - if (isminw) data.width = o.minWidth; - if (isminh) data.height = o.minHeight; - if (ismaxw) data.width = o.maxWidth; - if (ismaxh) data.height = o.maxHeight; - - var dw = this.originalPosition.left + this.originalSize.width, dh = this.position.top + this.size.height; - var cw = /sw|nw|w/.test(a), ch = /nw|ne|n/.test(a); - - if (isminw && cw) data.left = dw - o.minWidth; - if (ismaxw && cw) data.left = dw - o.maxWidth; - if (isminh && ch) data.top = dh - o.minHeight; - if (ismaxh && ch) data.top = dh - o.maxHeight; - - // fixing jump error on top/left - bug #2330 - var isNotwh = !data.width && !data.height; - if (isNotwh && !data.left && data.top) data.top = null; - else if (isNotwh && !data.top && data.left) data.left = null; - - return data; - }, - - _proportionallyResize: function() { - - var o = this.options; - if (!this._proportionallyResizeElements.length) return; - var element = this.helper || this.element; - - for (var i=0; i < this._proportionallyResizeElements.length; i++) { - - var prel = this._proportionallyResizeElements[i]; - - if (!this.borderDif) { - var b = [prel.css('borderTopWidth'), prel.css('borderRightWidth'), prel.css('borderBottomWidth'), prel.css('borderLeftWidth')], - p = [prel.css('paddingTop'), prel.css('paddingRight'), prel.css('paddingBottom'), prel.css('paddingLeft')]; - - this.borderDif = $.map(b, function(v, i) { - var border = parseInt(v,10)||0, padding = parseInt(p[i],10)||0; - return border + padding; - }); - } - - prel.css({ - height: (element.height() - this.borderDif[0] - this.borderDif[2]) || 0, - width: (element.width() - this.borderDif[1] - this.borderDif[3]) || 0 - }); - - }; - - }, - - _renderProxy: function() { - - var el = this.element, o = this.options; - this.elementOffset = el.offset(); - - if(this._helper) { - - this.helper = this.helper || $('
'); - - // fix ie6 offset TODO: This seems broken - var ie6offset = ($.ui.ie6 ? 1 : 0), - pxyoffset = ( $.ui.ie6 ? 2 : -1 ); - - this.helper.addClass(this._helper).css({ - width: this.element.outerWidth() + pxyoffset, - height: this.element.outerHeight() + pxyoffset, - position: 'absolute', - left: this.elementOffset.left - ie6offset +'px', - top: this.elementOffset.top - ie6offset +'px', - zIndex: ++o.zIndex //TODO: Don't modify option - }); - - this.helper - .appendTo("body") - .disableSelection(); - - } else { - this.helper = this.element; - } - - }, - - _change: { - e: function(event, dx, dy) { - return { width: this.originalSize.width + dx }; - }, - w: function(event, dx, dy) { - var o = this.options, cs = this.originalSize, sp = this.originalPosition; - return { left: sp.left + dx, width: cs.width - dx }; - }, - n: function(event, dx, dy) { - var o = this.options, cs = this.originalSize, sp = this.originalPosition; - return { top: sp.top + dy, height: cs.height - dy }; - }, - s: function(event, dx, dy) { - return { height: this.originalSize.height + dy }; - }, - se: function(event, dx, dy) { - return $.extend(this._change.s.apply(this, arguments), this._change.e.apply(this, [event, dx, dy])); - }, - sw: function(event, dx, dy) { - return $.extend(this._change.s.apply(this, arguments), this._change.w.apply(this, [event, dx, dy])); - }, - ne: function(event, dx, dy) { - return $.extend(this._change.n.apply(this, arguments), this._change.e.apply(this, [event, dx, dy])); - }, - nw: function(event, dx, dy) { - return $.extend(this._change.n.apply(this, arguments), this._change.w.apply(this, [event, dx, dy])); - } - }, - - _propagate: function(n, event) { - $.ui.plugin.call(this, n, [event, this.ui()]); - (n != "resize" && this._trigger(n, event, this.ui())); - }, - - plugins: {}, - - ui: function() { - return { - originalElement: this.originalElement, - element: this.element, - helper: this.helper, - position: this.position, - size: this.size, - originalSize: this.originalSize, - originalPosition: this.originalPosition - }; - } - -}); - -/* - * Resizable Extensions - */ - -$.ui.plugin.add("resizable", "alsoResize", { - - start: function (event, ui) { - var that = $(this).data("resizable"), o = that.options; - - var _store = function (exp) { - $(exp).each(function() { - var el = $(this); - el.data("resizable-alsoresize", { - width: parseInt(el.width(), 10), height: parseInt(el.height(), 10), - left: parseInt(el.css('left'), 10), top: parseInt(el.css('top'), 10) - }); - }); - }; - - if (typeof(o.alsoResize) == 'object' && !o.alsoResize.parentNode) { - if (o.alsoResize.length) { o.alsoResize = o.alsoResize[0]; _store(o.alsoResize); } - else { $.each(o.alsoResize, function (exp) { _store(exp); }); } - }else{ - _store(o.alsoResize); - } - }, - - resize: function (event, ui) { - var that = $(this).data("resizable"), o = that.options, os = that.originalSize, op = that.originalPosition; - - var delta = { - height: (that.size.height - os.height) || 0, width: (that.size.width - os.width) || 0, - top: (that.position.top - op.top) || 0, left: (that.position.left - op.left) || 0 - }, - - _alsoResize = function (exp, c) { - $(exp).each(function() { - var el = $(this), start = $(this).data("resizable-alsoresize"), style = {}, - css = c && c.length ? c : el.parents(ui.originalElement[0]).length ? ['width', 'height'] : ['width', 'height', 'top', 'left']; - - $.each(css, function (i, prop) { - var sum = (start[prop]||0) + (delta[prop]||0); - if (sum && sum >= 0) - style[prop] = sum || null; - }); - - el.css(style); - }); - }; - - if (typeof(o.alsoResize) == 'object' && !o.alsoResize.nodeType) { - $.each(o.alsoResize, function (exp, c) { _alsoResize(exp, c); }); - }else{ - _alsoResize(o.alsoResize); - } - }, - - stop: function (event, ui) { - $(this).removeData("resizable-alsoresize"); - } -}); - -$.ui.plugin.add("resizable", "animate", { - - stop: function(event, ui) { - var that = $(this).data("resizable"), o = that.options; - - var pr = that._proportionallyResizeElements, ista = pr.length && (/textarea/i).test(pr[0].nodeName), - soffseth = ista && $.ui.hasScroll(pr[0], 'left') /* TODO - jump height */ ? 0 : that.sizeDiff.height, - soffsetw = ista ? 0 : that.sizeDiff.width; - - var style = { width: (that.size.width - soffsetw), height: (that.size.height - soffseth) }, - left = (parseInt(that.element.css('left'), 10) + (that.position.left - that.originalPosition.left)) || null, - top = (parseInt(that.element.css('top'), 10) + (that.position.top - that.originalPosition.top)) || null; - - that.element.animate( - $.extend(style, top && left ? { top: top, left: left } : {}), { - duration: o.animateDuration, - easing: o.animateEasing, - step: function() { - - var data = { - width: parseInt(that.element.css('width'), 10), - height: parseInt(that.element.css('height'), 10), - top: parseInt(that.element.css('top'), 10), - left: parseInt(that.element.css('left'), 10) - }; - - if (pr && pr.length) $(pr[0]).css({ width: data.width, height: data.height }); - - // propagating resize, and updating values for each animation step - that._updateCache(data); - that._propagate("resize", event); - - } - } - ); - } - -}); - -$.ui.plugin.add("resizable", "containment", { - - start: function(event, ui) { - var that = $(this).data("resizable"), o = that.options, el = that.element; - var oc = o.containment, ce = (oc instanceof $) ? oc.get(0) : (/parent/.test(oc)) ? el.parent().get(0) : oc; - if (!ce) return; - - that.containerElement = $(ce); - - if (/document/.test(oc) || oc == document) { - that.containerOffset = { left: 0, top: 0 }; - that.containerPosition = { left: 0, top: 0 }; - - that.parentData = { - element: $(document), left: 0, top: 0, - width: $(document).width(), height: $(document).height() || document.body.parentNode.scrollHeight - }; - } - - // i'm a node, so compute top, left, right, bottom - else { - var element = $(ce), p = []; - $([ "Top", "Right", "Left", "Bottom" ]).each(function(i, name) { p[i] = num(element.css("padding" + name)); }); - - that.containerOffset = element.offset(); - that.containerPosition = element.position(); - that.containerSize = { height: (element.innerHeight() - p[3]), width: (element.innerWidth() - p[1]) }; - - var co = that.containerOffset, ch = that.containerSize.height, cw = that.containerSize.width, - width = ($.ui.hasScroll(ce, "left") ? ce.scrollWidth : cw ), height = ($.ui.hasScroll(ce) ? ce.scrollHeight : ch); - - that.parentData = { - element: ce, left: co.left, top: co.top, width: width, height: height - }; - } - }, - - resize: function(event, ui) { - var that = $(this).data("resizable"), o = that.options, - ps = that.containerSize, co = that.containerOffset, cs = that.size, cp = that.position, - pRatio = that._aspectRatio || event.shiftKey, cop = { top:0, left:0 }, ce = that.containerElement; - - if (ce[0] != document && (/static/).test(ce.css('position'))) cop = co; - - if (cp.left < (that._helper ? co.left : 0)) { - that.size.width = that.size.width + (that._helper ? (that.position.left - co.left) : (that.position.left - cop.left)); - if (pRatio) that.size.height = that.size.width / that.aspectRatio; - that.position.left = o.helper ? co.left : 0; - } - - if (cp.top < (that._helper ? co.top : 0)) { - that.size.height = that.size.height + (that._helper ? (that.position.top - co.top) : that.position.top); - if (pRatio) that.size.width = that.size.height * that.aspectRatio; - that.position.top = that._helper ? co.top : 0; - } - - that.offset.left = that.parentData.left+that.position.left; - that.offset.top = that.parentData.top+that.position.top; - - var woset = Math.abs( (that._helper ? that.offset.left - cop.left : (that.offset.left - cop.left)) + that.sizeDiff.width ), - hoset = Math.abs( (that._helper ? that.offset.top - cop.top : (that.offset.top - co.top)) + that.sizeDiff.height ); - - var isParent = that.containerElement.get(0) == that.element.parent().get(0), - isOffsetRelative = /relative|absolute/.test(that.containerElement.css('position')); - - if(isParent && isOffsetRelative) woset -= that.parentData.left; - - if (woset + that.size.width >= that.parentData.width) { - that.size.width = that.parentData.width - woset; - if (pRatio) that.size.height = that.size.width / that.aspectRatio; - } - - if (hoset + that.size.height >= that.parentData.height) { - that.size.height = that.parentData.height - hoset; - if (pRatio) that.size.width = that.size.height * that.aspectRatio; - } - }, - - stop: function(event, ui){ - var that = $(this).data("resizable"), o = that.options, cp = that.position, - co = that.containerOffset, cop = that.containerPosition, ce = that.containerElement; - - var helper = $(that.helper), ho = helper.offset(), w = helper.outerWidth() - that.sizeDiff.width, h = helper.outerHeight() - that.sizeDiff.height; - - if (that._helper && !o.animate && (/relative/).test(ce.css('position'))) - $(this).css({ left: ho.left - cop.left - co.left, width: w, height: h }); - - if (that._helper && !o.animate && (/static/).test(ce.css('position'))) - $(this).css({ left: ho.left - cop.left - co.left, width: w, height: h }); - - } -}); - -$.ui.plugin.add("resizable", "ghost", { - - start: function(event, ui) { - - var that = $(this).data("resizable"), o = that.options, cs = that.size; - - that.ghost = that.originalElement.clone(); - that.ghost - .css({ opacity: .25, display: 'block', position: 'relative', height: cs.height, width: cs.width, margin: 0, left: 0, top: 0 }) - .addClass('ui-resizable-ghost') - .addClass(typeof o.ghost == 'string' ? o.ghost : ''); - - that.ghost.appendTo(that.helper); - - }, - - resize: function(event, ui){ - var that = $(this).data("resizable"), o = that.options; - if (that.ghost) that.ghost.css({ position: 'relative', height: that.size.height, width: that.size.width }); - }, - - stop: function(event, ui){ - var that = $(this).data("resizable"), o = that.options; - if (that.ghost && that.helper) that.helper.get(0).removeChild(that.ghost.get(0)); - } - -}); - -$.ui.plugin.add("resizable", "grid", { - - resize: function(event, ui) { - var that = $(this).data("resizable"), o = that.options, cs = that.size, os = that.originalSize, op = that.originalPosition, a = that.axis, ratio = o._aspectRatio || event.shiftKey; - o.grid = typeof o.grid == "number" ? [o.grid, o.grid] : o.grid; - var ox = Math.round((cs.width - os.width) / (o.grid[0]||1)) * (o.grid[0]||1), oy = Math.round((cs.height - os.height) / (o.grid[1]||1)) * (o.grid[1]||1); - - if (/^(se|s|e)$/.test(a)) { - that.size.width = os.width + ox; - that.size.height = os.height + oy; - } - else if (/^(ne)$/.test(a)) { - that.size.width = os.width + ox; - that.size.height = os.height + oy; - that.position.top = op.top - oy; - } - else if (/^(sw)$/.test(a)) { - that.size.width = os.width + ox; - that.size.height = os.height + oy; - that.position.left = op.left - ox; - } - else { - that.size.width = os.width + ox; - that.size.height = os.height + oy; - that.position.top = op.top - oy; - that.position.left = op.left - ox; - } - } - -}); - -var num = function(v) { - return parseInt(v, 10) || 0; -}; - -var isNumber = function(value) { - return !isNaN(parseInt(value, 10)); -}; - -})(jQuery); - -(function( $, undefined ) { - -$.widget("ui.selectable", $.ui.mouse, { - version: "1.9.2", - options: { - appendTo: 'body', - autoRefresh: true, - distance: 0, - filter: '*', - tolerance: 'touch' - }, - _create: function() { - var that = this; - - this.element.addClass("ui-selectable"); - - this.dragged = false; - - // cache selectee children based on filter - var selectees; - this.refresh = function() { - selectees = $(that.options.filter, that.element[0]); - selectees.addClass("ui-selectee"); - selectees.each(function() { - var $this = $(this); - var pos = $this.offset(); - $.data(this, "selectable-item", { - element: this, - $element: $this, - left: pos.left, - top: pos.top, - right: pos.left + $this.outerWidth(), - bottom: pos.top + $this.outerHeight(), - startselected: false, - selected: $this.hasClass('ui-selected'), - selecting: $this.hasClass('ui-selecting'), - unselecting: $this.hasClass('ui-unselecting') - }); - }); - }; - this.refresh(); - - this.selectees = selectees.addClass("ui-selectee"); - - this._mouseInit(); - - this.helper = $("
"); - }, - - _destroy: function() { - this.selectees - .removeClass("ui-selectee") - .removeData("selectable-item"); - this.element - .removeClass("ui-selectable ui-selectable-disabled"); - this._mouseDestroy(); - }, - - _mouseStart: function(event) { - var that = this; - - this.opos = [event.pageX, event.pageY]; - - if (this.options.disabled) - return; - - var options = this.options; - - this.selectees = $(options.filter, this.element[0]); - - this._trigger("start", event); - - $(options.appendTo).append(this.helper); - // position helper (lasso) - this.helper.css({ - "left": event.clientX, - "top": event.clientY, - "width": 0, - "height": 0 - }); - - if (options.autoRefresh) { - this.refresh(); - } - - this.selectees.filter('.ui-selected').each(function() { - var selectee = $.data(this, "selectable-item"); - selectee.startselected = true; - if (!event.metaKey && !event.ctrlKey) { - selectee.$element.removeClass('ui-selected'); - selectee.selected = false; - selectee.$element.addClass('ui-unselecting'); - selectee.unselecting = true; - // selectable UNSELECTING callback - that._trigger("unselecting", event, { - unselecting: selectee.element - }); - } - }); - - $(event.target).parents().andSelf().each(function() { - var selectee = $.data(this, "selectable-item"); - if (selectee) { - var doSelect = (!event.metaKey && !event.ctrlKey) || !selectee.$element.hasClass('ui-selected'); - selectee.$element - .removeClass(doSelect ? "ui-unselecting" : "ui-selected") - .addClass(doSelect ? "ui-selecting" : "ui-unselecting"); - selectee.unselecting = !doSelect; - selectee.selecting = doSelect; - selectee.selected = doSelect; - // selectable (UN)SELECTING callback - if (doSelect) { - that._trigger("selecting", event, { - selecting: selectee.element - }); - } else { - that._trigger("unselecting", event, { - unselecting: selectee.element - }); - } - return false; - } - }); - - }, - - _mouseDrag: function(event) { - var that = this; - this.dragged = true; - - if (this.options.disabled) - return; - - var options = this.options; - - var x1 = this.opos[0], y1 = this.opos[1], x2 = event.pageX, y2 = event.pageY; - if (x1 > x2) { var tmp = x2; x2 = x1; x1 = tmp; } - if (y1 > y2) { var tmp = y2; y2 = y1; y1 = tmp; } - this.helper.css({left: x1, top: y1, width: x2-x1, height: y2-y1}); - - this.selectees.each(function() { - var selectee = $.data(this, "selectable-item"); - //prevent helper from being selected if appendTo: selectable - if (!selectee || selectee.element == that.element[0]) - return; - var hit = false; - if (options.tolerance == 'touch') { - hit = ( !(selectee.left > x2 || selectee.right < x1 || selectee.top > y2 || selectee.bottom < y1) ); - } else if (options.tolerance == 'fit') { - hit = (selectee.left > x1 && selectee.right < x2 && selectee.top > y1 && selectee.bottom < y2); - } - - if (hit) { - // SELECT - if (selectee.selected) { - selectee.$element.removeClass('ui-selected'); - selectee.selected = false; - } - if (selectee.unselecting) { - selectee.$element.removeClass('ui-unselecting'); - selectee.unselecting = false; - } - if (!selectee.selecting) { - selectee.$element.addClass('ui-selecting'); - selectee.selecting = true; - // selectable SELECTING callback - that._trigger("selecting", event, { - selecting: selectee.element - }); - } - } else { - // UNSELECT - if (selectee.selecting) { - if ((event.metaKey || event.ctrlKey) && selectee.startselected) { - selectee.$element.removeClass('ui-selecting'); - selectee.selecting = false; - selectee.$element.addClass('ui-selected'); - selectee.selected = true; - } else { - selectee.$element.removeClass('ui-selecting'); - selectee.selecting = false; - if (selectee.startselected) { - selectee.$element.addClass('ui-unselecting'); - selectee.unselecting = true; - } - // selectable UNSELECTING callback - that._trigger("unselecting", event, { - unselecting: selectee.element - }); - } - } - if (selectee.selected) { - if (!event.metaKey && !event.ctrlKey && !selectee.startselected) { - selectee.$element.removeClass('ui-selected'); - selectee.selected = false; - - selectee.$element.addClass('ui-unselecting'); - selectee.unselecting = true; - // selectable UNSELECTING callback - that._trigger("unselecting", event, { - unselecting: selectee.element - }); - } - } - } - }); - - return false; - }, - - _mouseStop: function(event) { - var that = this; - - this.dragged = false; - - var options = this.options; - - $('.ui-unselecting', this.element[0]).each(function() { - var selectee = $.data(this, "selectable-item"); - selectee.$element.removeClass('ui-unselecting'); - selectee.unselecting = false; - selectee.startselected = false; - that._trigger("unselected", event, { - unselected: selectee.element - }); - }); - $('.ui-selecting', this.element[0]).each(function() { - var selectee = $.data(this, "selectable-item"); - selectee.$element.removeClass('ui-selecting').addClass('ui-selected'); - selectee.selecting = false; - selectee.selected = true; - selectee.startselected = true; - that._trigger("selected", event, { - selected: selectee.element - }); - }); - this._trigger("stop", event); - - this.helper.remove(); - - return false; - } - -}); - -})(jQuery); - -(function( $, undefined ) { - -$.widget("ui.sortable", $.ui.mouse, { - version: "1.9.2", - widgetEventPrefix: "sort", - ready: false, - options: { - appendTo: "parent", - axis: false, - connectWith: false, - containment: false, - cursor: 'auto', - cursorAt: false, - dropOnEmpty: true, - forcePlaceholderSize: false, - forceHelperSize: false, - grid: false, - handle: false, - helper: "original", - items: '> *', - opacity: false, - placeholder: false, - revert: false, - scroll: true, - scrollSensitivity: 20, - scrollSpeed: 20, - scope: "default", - tolerance: "intersect", - zIndex: 1000 - }, - _create: function() { - - var o = this.options; - this.containerCache = {}; - this.element.addClass("ui-sortable"); - - //Get the items - this.refresh(); - - //Let's determine if the items are being displayed horizontally - this.floating = this.items.length ? o.axis === 'x' || (/left|right/).test(this.items[0].item.css('float')) || (/inline|table-cell/).test(this.items[0].item.css('display')) : false; - - //Let's determine the parent's offset - this.offset = this.element.offset(); - - //Initialize mouse events for interaction - this._mouseInit(); - - //We're ready to go - this.ready = true - - }, - - _destroy: function() { - this.element - .removeClass("ui-sortable ui-sortable-disabled"); - this._mouseDestroy(); - - for ( var i = this.items.length - 1; i >= 0; i-- ) - this.items[i].item.removeData(this.widgetName + "-item"); - - return this; - }, - - _setOption: function(key, value){ - if ( key === "disabled" ) { - this.options[ key ] = value; - - this.widget().toggleClass( "ui-sortable-disabled", !!value ); - } else { - // Don't call widget base _setOption for disable as it adds ui-state-disabled class - $.Widget.prototype._setOption.apply(this, arguments); - } - }, - - _mouseCapture: function(event, overrideHandle) { - var that = this; - - if (this.reverting) { - return false; - } - - if(this.options.disabled || this.options.type == 'static') return false; - - //We have to refresh the items data once first - this._refreshItems(event); - - //Find out if the clicked node (or one of its parents) is a actual item in this.items - var currentItem = null, nodes = $(event.target).parents().each(function() { - if($.data(this, that.widgetName + '-item') == that) { - currentItem = $(this); - return false; - } - }); - if($.data(event.target, that.widgetName + '-item') == that) currentItem = $(event.target); - - if(!currentItem) return false; - if(this.options.handle && !overrideHandle) { - var validHandle = false; - - $(this.options.handle, currentItem).find("*").andSelf().each(function() { if(this == event.target) validHandle = true; }); - if(!validHandle) return false; - } - - this.currentItem = currentItem; - this._removeCurrentsFromItems(); - return true; - - }, - - _mouseStart: function(event, overrideHandle, noActivation) { - - var o = this.options; - this.currentContainer = this; - - //We only need to call refreshPositions, because the refreshItems call has been moved to mouseCapture - this.refreshPositions(); - - //Create and append the visible helper - this.helper = this._createHelper(event); - - //Cache the helper size - this._cacheHelperProportions(); - - /* - * - Position generation - - * This block generates everything position related - it's the core of draggables. - */ - - //Cache the margins of the original element - this._cacheMargins(); - - //Get the next scrolling parent - this.scrollParent = this.helper.scrollParent(); - - //The element's absolute position on the page minus margins - this.offset = this.currentItem.offset(); - this.offset = { - top: this.offset.top - this.margins.top, - left: this.offset.left - this.margins.left - }; - - $.extend(this.offset, { - click: { //Where the click happened, relative to the element - left: event.pageX - this.offset.left, - top: event.pageY - this.offset.top - }, - parent: this._getParentOffset(), - relative: this._getRelativeOffset() //This is a relative to absolute position minus the actual position calculation - only used for relative positioned helper - }); - - // Only after we got the offset, we can change the helper's position to absolute - // TODO: Still need to figure out a way to make relative sorting possible - this.helper.css("position", "absolute"); - this.cssPosition = this.helper.css("position"); - - //Generate the original position - this.originalPosition = this._generatePosition(event); - this.originalPageX = event.pageX; - this.originalPageY = event.pageY; - - //Adjust the mouse offset relative to the helper if 'cursorAt' is supplied - (o.cursorAt && this._adjustOffsetFromHelper(o.cursorAt)); - - //Cache the former DOM position - this.domPosition = { prev: this.currentItem.prev()[0], parent: this.currentItem.parent()[0] }; - - //If the helper is not the original, hide the original so it's not playing any role during the drag, won't cause anything bad this way - if(this.helper[0] != this.currentItem[0]) { - this.currentItem.hide(); - } - - //Create the placeholder - this._createPlaceholder(); - - //Set a containment if given in the options - if(o.containment) - this._setContainment(); - - if(o.cursor) { // cursor option - if ($('body').css("cursor")) this._storedCursor = $('body').css("cursor"); - $('body').css("cursor", o.cursor); - } - - if(o.opacity) { // opacity option - if (this.helper.css("opacity")) this._storedOpacity = this.helper.css("opacity"); - this.helper.css("opacity", o.opacity); - } - - if(o.zIndex) { // zIndex option - if (this.helper.css("zIndex")) this._storedZIndex = this.helper.css("zIndex"); - this.helper.css("zIndex", o.zIndex); - } - - //Prepare scrolling - if(this.scrollParent[0] != document && this.scrollParent[0].tagName != 'HTML') - this.overflowOffset = this.scrollParent.offset(); - - //Call callbacks - this._trigger("start", event, this._uiHash()); - - //Recache the helper size - if(!this._preserveHelperProportions) - this._cacheHelperProportions(); - - - //Post 'activate' events to possible containers - if(!noActivation) { - for (var i = this.containers.length - 1; i >= 0; i--) { this.containers[i]._trigger("activate", event, this._uiHash(this)); } - } - - //Prepare possible droppables - if($.ui.ddmanager) - $.ui.ddmanager.current = this; - - if ($.ui.ddmanager && !o.dropBehaviour) - $.ui.ddmanager.prepareOffsets(this, event); - - this.dragging = true; - - this.helper.addClass("ui-sortable-helper"); - this._mouseDrag(event); //Execute the drag once - this causes the helper not to be visible before getting its correct position - return true; - - }, - - _mouseDrag: function(event) { - - //Compute the helpers position - this.position = this._generatePosition(event); - this.positionAbs = this._convertPositionTo("absolute"); - - if (!this.lastPositionAbs) { - this.lastPositionAbs = this.positionAbs; - } - - //Do scrolling - if(this.options.scroll) { - var o = this.options, scrolled = false; - if(this.scrollParent[0] != document && this.scrollParent[0].tagName != 'HTML') { - - if((this.overflowOffset.top + this.scrollParent[0].offsetHeight) - event.pageY < o.scrollSensitivity) - this.scrollParent[0].scrollTop = scrolled = this.scrollParent[0].scrollTop + o.scrollSpeed; - else if(event.pageY - this.overflowOffset.top < o.scrollSensitivity) - this.scrollParent[0].scrollTop = scrolled = this.scrollParent[0].scrollTop - o.scrollSpeed; - - if((this.overflowOffset.left + this.scrollParent[0].offsetWidth) - event.pageX < o.scrollSensitivity) - this.scrollParent[0].scrollLeft = scrolled = this.scrollParent[0].scrollLeft + o.scrollSpeed; - else if(event.pageX - this.overflowOffset.left < o.scrollSensitivity) - this.scrollParent[0].scrollLeft = scrolled = this.scrollParent[0].scrollLeft - o.scrollSpeed; - - } else { - - if(event.pageY - $(document).scrollTop() < o.scrollSensitivity) - scrolled = $(document).scrollTop($(document).scrollTop() - o.scrollSpeed); - else if($(window).height() - (event.pageY - $(document).scrollTop()) < o.scrollSensitivity) - scrolled = $(document).scrollTop($(document).scrollTop() + o.scrollSpeed); - - if(event.pageX - $(document).scrollLeft() < o.scrollSensitivity) - scrolled = $(document).scrollLeft($(document).scrollLeft() - o.scrollSpeed); - else if($(window).width() - (event.pageX - $(document).scrollLeft()) < o.scrollSensitivity) - scrolled = $(document).scrollLeft($(document).scrollLeft() + o.scrollSpeed); - - } - - if(scrolled !== false && $.ui.ddmanager && !o.dropBehaviour) - $.ui.ddmanager.prepareOffsets(this, event); - } - - //Regenerate the absolute position used for position checks - this.positionAbs = this._convertPositionTo("absolute"); - - //Set the helper position - if(!this.options.axis || this.options.axis != "y") this.helper[0].style.left = this.position.left+'px'; - if(!this.options.axis || this.options.axis != "x") this.helper[0].style.top = this.position.top+'px'; - - //Rearrange - for (var i = this.items.length - 1; i >= 0; i--) { - - //Cache variables and intersection, continue if no intersection - var item = this.items[i], itemElement = item.item[0], intersection = this._intersectsWithPointer(item); - if (!intersection) continue; - - // Only put the placeholder inside the current Container, skip all - // items form other containers. This works because when moving - // an item from one container to another the - // currentContainer is switched before the placeholder is moved. - // - // Without this moving items in "sub-sortables" can cause the placeholder to jitter - // beetween the outer and inner container. - if (item.instance !== this.currentContainer) continue; - - if (itemElement != this.currentItem[0] //cannot intersect with itself - && this.placeholder[intersection == 1 ? "next" : "prev"]()[0] != itemElement //no useless actions that have been done before - && !$.contains(this.placeholder[0], itemElement) //no action if the item moved is the parent of the item checked - && (this.options.type == 'semi-dynamic' ? !$.contains(this.element[0], itemElement) : true) - //&& itemElement.parentNode == this.placeholder[0].parentNode // only rearrange items within the same container - ) { - - this.direction = intersection == 1 ? "down" : "up"; - - if (this.options.tolerance == "pointer" || this._intersectsWithSides(item)) { - this._rearrange(event, item); - } else { - break; - } - - this._trigger("change", event, this._uiHash()); - break; - } - } - - //Post events to containers - this._contactContainers(event); - - //Interconnect with droppables - if($.ui.ddmanager) $.ui.ddmanager.drag(this, event); - - //Call callbacks - this._trigger('sort', event, this._uiHash()); - - this.lastPositionAbs = this.positionAbs; - return false; - - }, - - _mouseStop: function(event, noPropagation) { - - if(!event) return; - - //If we are using droppables, inform the manager about the drop - if ($.ui.ddmanager && !this.options.dropBehaviour) - $.ui.ddmanager.drop(this, event); - - if(this.options.revert) { - var that = this; - var cur = this.placeholder.offset(); - - this.reverting = true; - - $(this.helper).animate({ - left: cur.left - this.offset.parent.left - this.margins.left + (this.offsetParent[0] == document.body ? 0 : this.offsetParent[0].scrollLeft), - top: cur.top - this.offset.parent.top - this.margins.top + (this.offsetParent[0] == document.body ? 0 : this.offsetParent[0].scrollTop) - }, parseInt(this.options.revert, 10) || 500, function() { - that._clear(event); - }); - } else { - this._clear(event, noPropagation); - } - - return false; - - }, - - cancel: function() { - - if(this.dragging) { - - this._mouseUp({ target: null }); - - if(this.options.helper == "original") - this.currentItem.css(this._storedCSS).removeClass("ui-sortable-helper"); - else - this.currentItem.show(); - - //Post deactivating events to containers - for (var i = this.containers.length - 1; i >= 0; i--){ - this.containers[i]._trigger("deactivate", null, this._uiHash(this)); - if(this.containers[i].containerCache.over) { - this.containers[i]._trigger("out", null, this._uiHash(this)); - this.containers[i].containerCache.over = 0; - } - } - - } - - if (this.placeholder) { - //$(this.placeholder[0]).remove(); would have been the jQuery way - unfortunately, it unbinds ALL events from the original node! - if(this.placeholder[0].parentNode) this.placeholder[0].parentNode.removeChild(this.placeholder[0]); - if(this.options.helper != "original" && this.helper && this.helper[0].parentNode) this.helper.remove(); - - $.extend(this, { - helper: null, - dragging: false, - reverting: false, - _noFinalSort: null - }); - - if(this.domPosition.prev) { - $(this.domPosition.prev).after(this.currentItem); - } else { - $(this.domPosition.parent).prepend(this.currentItem); - } - } - - return this; - - }, - - serialize: function(o) { - - var items = this._getItemsAsjQuery(o && o.connected); - var str = []; o = o || {}; - - $(items).each(function() { - var res = ($(o.item || this).attr(o.attribute || 'id') || '').match(o.expression || (/(.+)[-=_](.+)/)); - if(res) str.push((o.key || res[1]+'[]')+'='+(o.key && o.expression ? res[1] : res[2])); - }); - - if(!str.length && o.key) { - str.push(o.key + '='); - } - - return str.join('&'); - - }, - - toArray: function(o) { - - var items = this._getItemsAsjQuery(o && o.connected); - var ret = []; o = o || {}; - - items.each(function() { ret.push($(o.item || this).attr(o.attribute || 'id') || ''); }); - return ret; - - }, - - /* Be careful with the following core functions */ - _intersectsWith: function(item) { - - var x1 = this.positionAbs.left, - x2 = x1 + this.helperProportions.width, - y1 = this.positionAbs.top, - y2 = y1 + this.helperProportions.height; - - var l = item.left, - r = l + item.width, - t = item.top, - b = t + item.height; - - var dyClick = this.offset.click.top, - dxClick = this.offset.click.left; - - var isOverElement = (y1 + dyClick) > t && (y1 + dyClick) < b && (x1 + dxClick) > l && (x1 + dxClick) < r; - - if( this.options.tolerance == "pointer" - || this.options.forcePointerForContainers - || (this.options.tolerance != "pointer" && this.helperProportions[this.floating ? 'width' : 'height'] > item[this.floating ? 'width' : 'height']) - ) { - return isOverElement; - } else { - - return (l < x1 + (this.helperProportions.width / 2) // Right Half - && x2 - (this.helperProportions.width / 2) < r // Left Half - && t < y1 + (this.helperProportions.height / 2) // Bottom Half - && y2 - (this.helperProportions.height / 2) < b ); // Top Half - - } - }, - - _intersectsWithPointer: function(item) { - - var isOverElementHeight = (this.options.axis === 'x') || $.ui.isOverAxis(this.positionAbs.top + this.offset.click.top, item.top, item.height), - isOverElementWidth = (this.options.axis === 'y') || $.ui.isOverAxis(this.positionAbs.left + this.offset.click.left, item.left, item.width), - isOverElement = isOverElementHeight && isOverElementWidth, - verticalDirection = this._getDragVerticalDirection(), - horizontalDirection = this._getDragHorizontalDirection(); - - if (!isOverElement) - return false; - - return this.floating ? - ( ((horizontalDirection && horizontalDirection == "right") || verticalDirection == "down") ? 2 : 1 ) - : ( verticalDirection && (verticalDirection == "down" ? 2 : 1) ); - - }, - - _intersectsWithSides: function(item) { - - var isOverBottomHalf = $.ui.isOverAxis(this.positionAbs.top + this.offset.click.top, item.top + (item.height/2), item.height), - isOverRightHalf = $.ui.isOverAxis(this.positionAbs.left + this.offset.click.left, item.left + (item.width/2), item.width), - verticalDirection = this._getDragVerticalDirection(), - horizontalDirection = this._getDragHorizontalDirection(); - - if (this.floating && horizontalDirection) { - return ((horizontalDirection == "right" && isOverRightHalf) || (horizontalDirection == "left" && !isOverRightHalf)); - } else { - return verticalDirection && ((verticalDirection == "down" && isOverBottomHalf) || (verticalDirection == "up" && !isOverBottomHalf)); - } - - }, - - _getDragVerticalDirection: function() { - var delta = this.positionAbs.top - this.lastPositionAbs.top; - return delta != 0 && (delta > 0 ? "down" : "up"); - }, - - _getDragHorizontalDirection: function() { - var delta = this.positionAbs.left - this.lastPositionAbs.left; - return delta != 0 && (delta > 0 ? "right" : "left"); - }, - - refresh: function(event) { - this._refreshItems(event); - this.refreshPositions(); - return this; - }, - - _connectWith: function() { - var options = this.options; - return options.connectWith.constructor == String - ? [options.connectWith] - : options.connectWith; - }, - - _getItemsAsjQuery: function(connected) { - - var items = []; - var queries = []; - var connectWith = this._connectWith(); - - if(connectWith && connected) { - for (var i = connectWith.length - 1; i >= 0; i--){ - var cur = $(connectWith[i]); - for (var j = cur.length - 1; j >= 0; j--){ - var inst = $.data(cur[j], this.widgetName); - if(inst && inst != this && !inst.options.disabled) { - queries.push([$.isFunction(inst.options.items) ? inst.options.items.call(inst.element) : $(inst.options.items, inst.element).not(".ui-sortable-helper").not('.ui-sortable-placeholder'), inst]); - } - }; - }; - } - - queries.push([$.isFunction(this.options.items) ? this.options.items.call(this.element, null, { options: this.options, item: this.currentItem }) : $(this.options.items, this.element).not(".ui-sortable-helper").not('.ui-sortable-placeholder'), this]); - - for (var i = queries.length - 1; i >= 0; i--){ - queries[i][0].each(function() { - items.push(this); - }); - }; - - return $(items); - - }, - - _removeCurrentsFromItems: function() { - - var list = this.currentItem.find(":data(" + this.widgetName + "-item)"); - - this.items = $.grep(this.items, function (item) { - for (var j=0; j < list.length; j++) { - if(list[j] == item.item[0]) - return false; - }; - return true; - }); - - }, - - _refreshItems: function(event) { - - this.items = []; - this.containers = [this]; - var items = this.items; - var queries = [[$.isFunction(this.options.items) ? this.options.items.call(this.element[0], event, { item: this.currentItem }) : $(this.options.items, this.element), this]]; - var connectWith = this._connectWith(); - - if(connectWith && this.ready) { //Shouldn't be run the first time through due to massive slow-down - for (var i = connectWith.length - 1; i >= 0; i--){ - var cur = $(connectWith[i]); - for (var j = cur.length - 1; j >= 0; j--){ - var inst = $.data(cur[j], this.widgetName); - if(inst && inst != this && !inst.options.disabled) { - queries.push([$.isFunction(inst.options.items) ? inst.options.items.call(inst.element[0], event, { item: this.currentItem }) : $(inst.options.items, inst.element), inst]); - this.containers.push(inst); - } - }; - }; - } - - for (var i = queries.length - 1; i >= 0; i--) { - var targetData = queries[i][1]; - var _queries = queries[i][0]; - - for (var j=0, queriesLength = _queries.length; j < queriesLength; j++) { - var item = $(_queries[j]); - - item.data(this.widgetName + '-item', targetData); // Data for target checking (mouse manager) - - items.push({ - item: item, - instance: targetData, - width: 0, height: 0, - left: 0, top: 0 - }); - }; - }; - - }, - - refreshPositions: function(fast) { - - //This has to be redone because due to the item being moved out/into the offsetParent, the offsetParent's position will change - if(this.offsetParent && this.helper) { - this.offset.parent = this._getParentOffset(); - } - - for (var i = this.items.length - 1; i >= 0; i--){ - var item = this.items[i]; - - //We ignore calculating positions of all connected containers when we're not over them - if(item.instance != this.currentContainer && this.currentContainer && item.item[0] != this.currentItem[0]) - continue; - - var t = this.options.toleranceElement ? $(this.options.toleranceElement, item.item) : item.item; - - if (!fast) { - item.width = t.outerWidth(); - item.height = t.outerHeight(); - } - - var p = t.offset(); - item.left = p.left; - item.top = p.top; - }; - - if(this.options.custom && this.options.custom.refreshContainers) { - this.options.custom.refreshContainers.call(this); - } else { - for (var i = this.containers.length - 1; i >= 0; i--){ - var p = this.containers[i].element.offset(); - this.containers[i].containerCache.left = p.left; - this.containers[i].containerCache.top = p.top; - this.containers[i].containerCache.width = this.containers[i].element.outerWidth(); - this.containers[i].containerCache.height = this.containers[i].element.outerHeight(); - }; - } - - return this; - }, - - _createPlaceholder: function(that) { - that = that || this; - var o = that.options; - - if(!o.placeholder || o.placeholder.constructor == String) { - var className = o.placeholder; - o.placeholder = { - element: function() { - - var el = $(document.createElement(that.currentItem[0].nodeName)) - .addClass(className || that.currentItem[0].className+" ui-sortable-placeholder") - .removeClass("ui-sortable-helper")[0]; - - if(!className) - el.style.visibility = "hidden"; - - return el; - }, - update: function(container, p) { - - // 1. If a className is set as 'placeholder option, we don't force sizes - the class is responsible for that - // 2. The option 'forcePlaceholderSize can be enabled to force it even if a class name is specified - if(className && !o.forcePlaceholderSize) return; - - //If the element doesn't have a actual height by itself (without styles coming from a stylesheet), it receives the inline height from the dragged item - if(!p.height()) { p.height(that.currentItem.innerHeight() - parseInt(that.currentItem.css('paddingTop')||0, 10) - parseInt(that.currentItem.css('paddingBottom')||0, 10)); }; - if(!p.width()) { p.width(that.currentItem.innerWidth() - parseInt(that.currentItem.css('paddingLeft')||0, 10) - parseInt(that.currentItem.css('paddingRight')||0, 10)); }; - } - }; - } - - //Create the placeholder - that.placeholder = $(o.placeholder.element.call(that.element, that.currentItem)); - - //Append it after the actual current item - that.currentItem.after(that.placeholder); - - //Update the size of the placeholder (TODO: Logic to fuzzy, see line 316/317) - o.placeholder.update(that, that.placeholder); - - }, - - _contactContainers: function(event) { - - // get innermost container that intersects with item - var innermostContainer = null, innermostIndex = null; - - - for (var i = this.containers.length - 1; i >= 0; i--){ - - // never consider a container that's located within the item itself - if($.contains(this.currentItem[0], this.containers[i].element[0])) - continue; - - if(this._intersectsWith(this.containers[i].containerCache)) { - - // if we've already found a container and it's more "inner" than this, then continue - if(innermostContainer && $.contains(this.containers[i].element[0], innermostContainer.element[0])) - continue; - - innermostContainer = this.containers[i]; - innermostIndex = i; - - } else { - // container doesn't intersect. trigger "out" event if necessary - if(this.containers[i].containerCache.over) { - this.containers[i]._trigger("out", event, this._uiHash(this)); - this.containers[i].containerCache.over = 0; - } - } - - } - - // if no intersecting containers found, return - if(!innermostContainer) return; - - // move the item into the container if it's not there already - if(this.containers.length === 1) { - this.containers[innermostIndex]._trigger("over", event, this._uiHash(this)); - this.containers[innermostIndex].containerCache.over = 1; - } else { - - //When entering a new container, we will find the item with the least distance and append our item near it - var dist = 10000; var itemWithLeastDistance = null; - var posProperty = this.containers[innermostIndex].floating ? 'left' : 'top'; - var sizeProperty = this.containers[innermostIndex].floating ? 'width' : 'height'; - var base = this.positionAbs[posProperty] + this.offset.click[posProperty]; - for (var j = this.items.length - 1; j >= 0; j--) { - if(!$.contains(this.containers[innermostIndex].element[0], this.items[j].item[0])) continue; - if(this.items[j].item[0] == this.currentItem[0]) continue; - var cur = this.items[j].item.offset()[posProperty]; - var nearBottom = false; - if(Math.abs(cur - base) > Math.abs(cur + this.items[j][sizeProperty] - base)){ - nearBottom = true; - cur += this.items[j][sizeProperty]; - } - - if(Math.abs(cur - base) < dist) { - dist = Math.abs(cur - base); itemWithLeastDistance = this.items[j]; - this.direction = nearBottom ? "up": "down"; - } - } - - if(!itemWithLeastDistance && !this.options.dropOnEmpty) //Check if dropOnEmpty is enabled - return; - - this.currentContainer = this.containers[innermostIndex]; - itemWithLeastDistance ? this._rearrange(event, itemWithLeastDistance, null, true) : this._rearrange(event, null, this.containers[innermostIndex].element, true); - this._trigger("change", event, this._uiHash()); - this.containers[innermostIndex]._trigger("change", event, this._uiHash(this)); - - //Update the placeholder - this.options.placeholder.update(this.currentContainer, this.placeholder); - - this.containers[innermostIndex]._trigger("over", event, this._uiHash(this)); - this.containers[innermostIndex].containerCache.over = 1; - } - - - }, - - _createHelper: function(event) { - - var o = this.options; - var helper = $.isFunction(o.helper) ? $(o.helper.apply(this.element[0], [event, this.currentItem])) : (o.helper == 'clone' ? this.currentItem.clone() : this.currentItem); - - if(!helper.parents('body').length) //Add the helper to the DOM if that didn't happen already - $(o.appendTo != 'parent' ? o.appendTo : this.currentItem[0].parentNode)[0].appendChild(helper[0]); - - if(helper[0] == this.currentItem[0]) - this._storedCSS = { width: this.currentItem[0].style.width, height: this.currentItem[0].style.height, position: this.currentItem.css("position"), top: this.currentItem.css("top"), left: this.currentItem.css("left") }; - - if(helper[0].style.width == '' || o.forceHelperSize) helper.width(this.currentItem.width()); - if(helper[0].style.height == '' || o.forceHelperSize) helper.height(this.currentItem.height()); - - return helper; - - }, - - _adjustOffsetFromHelper: function(obj) { - if (typeof obj == 'string') { - obj = obj.split(' '); - } - if ($.isArray(obj)) { - obj = {left: +obj[0], top: +obj[1] || 0}; - } - if ('left' in obj) { - this.offset.click.left = obj.left + this.margins.left; - } - if ('right' in obj) { - this.offset.click.left = this.helperProportions.width - obj.right + this.margins.left; - } - if ('top' in obj) { - this.offset.click.top = obj.top + this.margins.top; - } - if ('bottom' in obj) { - this.offset.click.top = this.helperProportions.height - obj.bottom + this.margins.top; - } - }, - - _getParentOffset: function() { - - - //Get the offsetParent and cache its position - this.offsetParent = this.helper.offsetParent(); - var po = this.offsetParent.offset(); - - // This is a special case where we need to modify a offset calculated on start, since the following happened: - // 1. The position of the helper is absolute, so it's position is calculated based on the next positioned parent - // 2. The actual offset parent is a child of the scroll parent, and the scroll parent isn't the document, which means that - // the scroll is included in the initial calculation of the offset of the parent, and never recalculated upon drag - if(this.cssPosition == 'absolute' && this.scrollParent[0] != document && $.contains(this.scrollParent[0], this.offsetParent[0])) { - po.left += this.scrollParent.scrollLeft(); - po.top += this.scrollParent.scrollTop(); - } - - if((this.offsetParent[0] == document.body) //This needs to be actually done for all browsers, since pageX/pageY includes this information - || (this.offsetParent[0].tagName && this.offsetParent[0].tagName.toLowerCase() == 'html' && $.ui.ie)) //Ugly IE fix - po = { top: 0, left: 0 }; - - return { - top: po.top + (parseInt(this.offsetParent.css("borderTopWidth"),10) || 0), - left: po.left + (parseInt(this.offsetParent.css("borderLeftWidth"),10) || 0) - }; - - }, - - _getRelativeOffset: function() { - - if(this.cssPosition == "relative") { - var p = this.currentItem.position(); - return { - top: p.top - (parseInt(this.helper.css("top"),10) || 0) + this.scrollParent.scrollTop(), - left: p.left - (parseInt(this.helper.css("left"),10) || 0) + this.scrollParent.scrollLeft() - }; - } else { - return { top: 0, left: 0 }; - } - - }, - - _cacheMargins: function() { - this.margins = { - left: (parseInt(this.currentItem.css("marginLeft"),10) || 0), - top: (parseInt(this.currentItem.css("marginTop"),10) || 0) - }; - }, - - _cacheHelperProportions: function() { - this.helperProportions = { - width: this.helper.outerWidth(), - height: this.helper.outerHeight() - }; - }, - - _setContainment: function() { - - var o = this.options; - if(o.containment == 'parent') o.containment = this.helper[0].parentNode; - if(o.containment == 'document' || o.containment == 'window') this.containment = [ - 0 - this.offset.relative.left - this.offset.parent.left, - 0 - this.offset.relative.top - this.offset.parent.top, - $(o.containment == 'document' ? document : window).width() - this.helperProportions.width - this.margins.left, - ($(o.containment == 'document' ? document : window).height() || document.body.parentNode.scrollHeight) - this.helperProportions.height - this.margins.top - ]; - - if(!(/^(document|window|parent)$/).test(o.containment)) { - var ce = $(o.containment)[0]; - var co = $(o.containment).offset(); - var over = ($(ce).css("overflow") != 'hidden'); - - this.containment = [ - co.left + (parseInt($(ce).css("borderLeftWidth"),10) || 0) + (parseInt($(ce).css("paddingLeft"),10) || 0) - this.margins.left, - co.top + (parseInt($(ce).css("borderTopWidth"),10) || 0) + (parseInt($(ce).css("paddingTop"),10) || 0) - this.margins.top, - co.left+(over ? Math.max(ce.scrollWidth,ce.offsetWidth) : ce.offsetWidth) - (parseInt($(ce).css("borderLeftWidth"),10) || 0) - (parseInt($(ce).css("paddingRight"),10) || 0) - this.helperProportions.width - this.margins.left, - co.top+(over ? Math.max(ce.scrollHeight,ce.offsetHeight) : ce.offsetHeight) - (parseInt($(ce).css("borderTopWidth"),10) || 0) - (parseInt($(ce).css("paddingBottom"),10) || 0) - this.helperProportions.height - this.margins.top - ]; - } - - }, - - _convertPositionTo: function(d, pos) { - - if(!pos) pos = this.position; - var mod = d == "absolute" ? 1 : -1; - var o = this.options, scroll = this.cssPosition == 'absolute' && !(this.scrollParent[0] != document && $.contains(this.scrollParent[0], this.offsetParent[0])) ? this.offsetParent : this.scrollParent, scrollIsRootNode = (/(html|body)/i).test(scroll[0].tagName); - - return { - top: ( - pos.top // The absolute mouse position - + this.offset.relative.top * mod // Only for relative positioned nodes: Relative offset from element to offset parent - + this.offset.parent.top * mod // The offsetParent's offset without borders (offset + border) - - ( ( this.cssPosition == 'fixed' ? -this.scrollParent.scrollTop() : ( scrollIsRootNode ? 0 : scroll.scrollTop() ) ) * mod) - ), - left: ( - pos.left // The absolute mouse position - + this.offset.relative.left * mod // Only for relative positioned nodes: Relative offset from element to offset parent - + this.offset.parent.left * mod // The offsetParent's offset without borders (offset + border) - - ( ( this.cssPosition == 'fixed' ? -this.scrollParent.scrollLeft() : scrollIsRootNode ? 0 : scroll.scrollLeft() ) * mod) - ) - }; - - }, - - _generatePosition: function(event) { - - var o = this.options, scroll = this.cssPosition == 'absolute' && !(this.scrollParent[0] != document && $.contains(this.scrollParent[0], this.offsetParent[0])) ? this.offsetParent : this.scrollParent, scrollIsRootNode = (/(html|body)/i).test(scroll[0].tagName); - - // This is another very weird special case that only happens for relative elements: - // 1. If the css position is relative - // 2. and the scroll parent is the document or similar to the offset parent - // we have to refresh the relative offset during the scroll so there are no jumps - if(this.cssPosition == 'relative' && !(this.scrollParent[0] != document && this.scrollParent[0] != this.offsetParent[0])) { - this.offset.relative = this._getRelativeOffset(); - } - - var pageX = event.pageX; - var pageY = event.pageY; - - /* - * - Position constraining - - * Constrain the position to a mix of grid, containment. - */ - - if(this.originalPosition) { //If we are not dragging yet, we won't check for options - - if(this.containment) { - if(event.pageX - this.offset.click.left < this.containment[0]) pageX = this.containment[0] + this.offset.click.left; - if(event.pageY - this.offset.click.top < this.containment[1]) pageY = this.containment[1] + this.offset.click.top; - if(event.pageX - this.offset.click.left > this.containment[2]) pageX = this.containment[2] + this.offset.click.left; - if(event.pageY - this.offset.click.top > this.containment[3]) pageY = this.containment[3] + this.offset.click.top; - } - - if(o.grid) { - var top = this.originalPageY + Math.round((pageY - this.originalPageY) / o.grid[1]) * o.grid[1]; - pageY = this.containment ? (!(top - this.offset.click.top < this.containment[1] || top - this.offset.click.top > this.containment[3]) ? top : (!(top - this.offset.click.top < this.containment[1]) ? top - o.grid[1] : top + o.grid[1])) : top; - - var left = this.originalPageX + Math.round((pageX - this.originalPageX) / o.grid[0]) * o.grid[0]; - pageX = this.containment ? (!(left - this.offset.click.left < this.containment[0] || left - this.offset.click.left > this.containment[2]) ? left : (!(left - this.offset.click.left < this.containment[0]) ? left - o.grid[0] : left + o.grid[0])) : left; - } - - } - - return { - top: ( - pageY // The absolute mouse position - - this.offset.click.top // Click offset (relative to the element) - - this.offset.relative.top // Only for relative positioned nodes: Relative offset from element to offset parent - - this.offset.parent.top // The offsetParent's offset without borders (offset + border) - + ( ( this.cssPosition == 'fixed' ? -this.scrollParent.scrollTop() : ( scrollIsRootNode ? 0 : scroll.scrollTop() ) )) - ), - left: ( - pageX // The absolute mouse position - - this.offset.click.left // Click offset (relative to the element) - - this.offset.relative.left // Only for relative positioned nodes: Relative offset from element to offset parent - - this.offset.parent.left // The offsetParent's offset without borders (offset + border) - + ( ( this.cssPosition == 'fixed' ? -this.scrollParent.scrollLeft() : scrollIsRootNode ? 0 : scroll.scrollLeft() )) - ) - }; - - }, - - _rearrange: function(event, i, a, hardRefresh) { - - a ? a[0].appendChild(this.placeholder[0]) : i.item[0].parentNode.insertBefore(this.placeholder[0], (this.direction == 'down' ? i.item[0] : i.item[0].nextSibling)); - - //Various things done here to improve the performance: - // 1. we create a setTimeout, that calls refreshPositions - // 2. on the instance, we have a counter variable, that get's higher after every append - // 3. on the local scope, we copy the counter variable, and check in the timeout, if it's still the same - // 4. this lets only the last addition to the timeout stack through - this.counter = this.counter ? ++this.counter : 1; - var counter = this.counter; - - this._delay(function() { - if(counter == this.counter) this.refreshPositions(!hardRefresh); //Precompute after each DOM insertion, NOT on mousemove - }); - - }, - - _clear: function(event, noPropagation) { - - this.reverting = false; - // We delay all events that have to be triggered to after the point where the placeholder has been removed and - // everything else normalized again - var delayedTriggers = []; - - // We first have to update the dom position of the actual currentItem - // Note: don't do it if the current item is already removed (by a user), or it gets reappended (see #4088) - if(!this._noFinalSort && this.currentItem.parent().length) this.placeholder.before(this.currentItem); - this._noFinalSort = null; - - if(this.helper[0] == this.currentItem[0]) { - for(var i in this._storedCSS) { - if(this._storedCSS[i] == 'auto' || this._storedCSS[i] == 'static') this._storedCSS[i] = ''; - } - this.currentItem.css(this._storedCSS).removeClass("ui-sortable-helper"); - } else { - this.currentItem.show(); - } - - if(this.fromOutside && !noPropagation) delayedTriggers.push(function(event) { this._trigger("receive", event, this._uiHash(this.fromOutside)); }); - if((this.fromOutside || this.domPosition.prev != this.currentItem.prev().not(".ui-sortable-helper")[0] || this.domPosition.parent != this.currentItem.parent()[0]) && !noPropagation) delayedTriggers.push(function(event) { this._trigger("update", event, this._uiHash()); }); //Trigger update callback if the DOM position has changed - - // Check if the items Container has Changed and trigger appropriate - // events. - if (this !== this.currentContainer) { - if(!noPropagation) { - delayedTriggers.push(function(event) { this._trigger("remove", event, this._uiHash()); }); - delayedTriggers.push((function(c) { return function(event) { c._trigger("receive", event, this._uiHash(this)); }; }).call(this, this.currentContainer)); - delayedTriggers.push((function(c) { return function(event) { c._trigger("update", event, this._uiHash(this)); }; }).call(this, this.currentContainer)); - } - } - - - //Post events to containers - for (var i = this.containers.length - 1; i >= 0; i--){ - if(!noPropagation) delayedTriggers.push((function(c) { return function(event) { c._trigger("deactivate", event, this._uiHash(this)); }; }).call(this, this.containers[i])); - if(this.containers[i].containerCache.over) { - delayedTriggers.push((function(c) { return function(event) { c._trigger("out", event, this._uiHash(this)); }; }).call(this, this.containers[i])); - this.containers[i].containerCache.over = 0; - } - } - - //Do what was originally in plugins - if(this._storedCursor) $('body').css("cursor", this._storedCursor); //Reset cursor - if(this._storedOpacity) this.helper.css("opacity", this._storedOpacity); //Reset opacity - if(this._storedZIndex) this.helper.css("zIndex", this._storedZIndex == 'auto' ? '' : this._storedZIndex); //Reset z-index - - this.dragging = false; - if(this.cancelHelperRemoval) { - if(!noPropagation) { - this._trigger("beforeStop", event, this._uiHash()); - for (var i=0; i < delayedTriggers.length; i++) { delayedTriggers[i].call(this, event); }; //Trigger all delayed events - this._trigger("stop", event, this._uiHash()); - } - - this.fromOutside = false; - return false; - } - - if(!noPropagation) this._trigger("beforeStop", event, this._uiHash()); - - //$(this.placeholder[0]).remove(); would have been the jQuery way - unfortunately, it unbinds ALL events from the original node! - this.placeholder[0].parentNode.removeChild(this.placeholder[0]); - - if(this.helper[0] != this.currentItem[0]) this.helper.remove(); this.helper = null; - - if(!noPropagation) { - for (var i=0; i < delayedTriggers.length; i++) { delayedTriggers[i].call(this, event); }; //Trigger all delayed events - this._trigger("stop", event, this._uiHash()); - } - - this.fromOutside = false; - return true; - - }, - - _trigger: function() { - if ($.Widget.prototype._trigger.apply(this, arguments) === false) { - this.cancel(); - } - }, - - _uiHash: function(_inst) { - var inst = _inst || this; - return { - helper: inst.helper, - placeholder: inst.placeholder || $([]), - position: inst.position, - originalPosition: inst.originalPosition, - offset: inst.positionAbs, - item: inst.currentItem, - sender: _inst ? _inst.element : null - }; - } - -}); - -})(jQuery); - -;(jQuery.effects || (function($, undefined) { - -var backCompat = $.uiBackCompat !== false, - // prefix used for storing data on .data() - dataSpace = "ui-effects-"; - -$.effects = { - effect: {} -}; - -/*! - * jQuery Color Animations v2.0.0 - * http://jquery.com/ - * - * Copyright 2012 jQuery Foundation and other contributors - * Released under the MIT license. - * http://jquery.org/license - * - * Date: Mon Aug 13 13:41:02 2012 -0500 - */ -(function( jQuery, undefined ) { - - var stepHooks = "backgroundColor borderBottomColor borderLeftColor borderRightColor borderTopColor color columnRuleColor outlineColor textDecorationColor textEmphasisColor".split(" "), - - // plusequals test for += 100 -= 100 - rplusequals = /^([\-+])=\s*(\d+\.?\d*)/, - // a set of RE's that can match strings and generate color tuples. - stringParsers = [{ - re: /rgba?\(\s*(\d{1,3})\s*,\s*(\d{1,3})\s*,\s*(\d{1,3})\s*(?:,\s*(\d+(?:\.\d+)?)\s*)?\)/, - parse: function( execResult ) { - return [ - execResult[ 1 ], - execResult[ 2 ], - execResult[ 3 ], - execResult[ 4 ] - ]; - } - }, { - re: /rgba?\(\s*(\d+(?:\.\d+)?)\%\s*,\s*(\d+(?:\.\d+)?)\%\s*,\s*(\d+(?:\.\d+)?)\%\s*(?:,\s*(\d+(?:\.\d+)?)\s*)?\)/, - parse: function( execResult ) { - return [ - execResult[ 1 ] * 2.55, - execResult[ 2 ] * 2.55, - execResult[ 3 ] * 2.55, - execResult[ 4 ] - ]; - } - }, { - // this regex ignores A-F because it's compared against an already lowercased string - re: /#([a-f0-9]{2})([a-f0-9]{2})([a-f0-9]{2})/, - parse: function( execResult ) { - return [ - parseInt( execResult[ 1 ], 16 ), - parseInt( execResult[ 2 ], 16 ), - parseInt( execResult[ 3 ], 16 ) - ]; - } - }, { - // this regex ignores A-F because it's compared against an already lowercased string - re: /#([a-f0-9])([a-f0-9])([a-f0-9])/, - parse: function( execResult ) { - return [ - parseInt( execResult[ 1 ] + execResult[ 1 ], 16 ), - parseInt( execResult[ 2 ] + execResult[ 2 ], 16 ), - parseInt( execResult[ 3 ] + execResult[ 3 ], 16 ) - ]; - } - }, { - re: /hsla?\(\s*(\d+(?:\.\d+)?)\s*,\s*(\d+(?:\.\d+)?)\%\s*,\s*(\d+(?:\.\d+)?)\%\s*(?:,\s*(\d+(?:\.\d+)?)\s*)?\)/, - space: "hsla", - parse: function( execResult ) { - return [ - execResult[ 1 ], - execResult[ 2 ] / 100, - execResult[ 3 ] / 100, - execResult[ 4 ] - ]; - } - }], - - // jQuery.Color( ) - color = jQuery.Color = function( color, green, blue, alpha ) { - return new jQuery.Color.fn.parse( color, green, blue, alpha ); - }, - spaces = { - rgba: { - props: { - red: { - idx: 0, - type: "byte" - }, - green: { - idx: 1, - type: "byte" - }, - blue: { - idx: 2, - type: "byte" - } - } - }, - - hsla: { - props: { - hue: { - idx: 0, - type: "degrees" - }, - saturation: { - idx: 1, - type: "percent" - }, - lightness: { - idx: 2, - type: "percent" - } - } - } - }, - propTypes = { - "byte": { - floor: true, - max: 255 - }, - "percent": { - max: 1 - }, - "degrees": { - mod: 360, - floor: true - } - }, - support = color.support = {}, - - // element for support tests - supportElem = jQuery( "

" )[ 0 ], - - // colors = jQuery.Color.names - colors, - - // local aliases of functions called often - each = jQuery.each; - -// determine rgba support immediately -supportElem.style.cssText = "background-color:rgba(1,1,1,.5)"; -support.rgba = supportElem.style.backgroundColor.indexOf( "rgba" ) > -1; - -// define cache name and alpha properties -// for rgba and hsla spaces -each( spaces, function( spaceName, space ) { - space.cache = "_" + spaceName; - space.props.alpha = { - idx: 3, - type: "percent", - def: 1 - }; -}); - -function clamp( value, prop, allowEmpty ) { - var type = propTypes[ prop.type ] || {}; - - if ( value == null ) { - return (allowEmpty || !prop.def) ? null : prop.def; - } - - // ~~ is an short way of doing floor for positive numbers - value = type.floor ? ~~value : parseFloat( value ); - - // IE will pass in empty strings as value for alpha, - // which will hit this case - if ( isNaN( value ) ) { - return prop.def; - } - - if ( type.mod ) { - // we add mod before modding to make sure that negatives values - // get converted properly: -10 -> 350 - return (value + type.mod) % type.mod; - } - - // for now all property types without mod have min and max - return 0 > value ? 0 : type.max < value ? type.max : value; -} - -function stringParse( string ) { - var inst = color(), - rgba = inst._rgba = []; - - string = string.toLowerCase(); - - each( stringParsers, function( i, parser ) { - var parsed, - match = parser.re.exec( string ), - values = match && parser.parse( match ), - spaceName = parser.space || "rgba"; - - if ( values ) { - parsed = inst[ spaceName ]( values ); - - // if this was an rgba parse the assignment might happen twice - // oh well.... - inst[ spaces[ spaceName ].cache ] = parsed[ spaces[ spaceName ].cache ]; - rgba = inst._rgba = parsed._rgba; - - // exit each( stringParsers ) here because we matched - return false; - } - }); - - // Found a stringParser that handled it - if ( rgba.length ) { - - // if this came from a parsed string, force "transparent" when alpha is 0 - // chrome, (and maybe others) return "transparent" as rgba(0,0,0,0) - if ( rgba.join() === "0,0,0,0" ) { - jQuery.extend( rgba, colors.transparent ); - } - return inst; - } - - // named colors - return colors[ string ]; -} - -color.fn = jQuery.extend( color.prototype, { - parse: function( red, green, blue, alpha ) { - if ( red === undefined ) { - this._rgba = [ null, null, null, null ]; - return this; - } - if ( red.jquery || red.nodeType ) { - red = jQuery( red ).css( green ); - green = undefined; - } - - var inst = this, - type = jQuery.type( red ), - rgba = this._rgba = []; - - // more than 1 argument specified - assume ( red, green, blue, alpha ) - if ( green !== undefined ) { - red = [ red, green, blue, alpha ]; - type = "array"; - } - - if ( type === "string" ) { - return this.parse( stringParse( red ) || colors._default ); - } - - if ( type === "array" ) { - each( spaces.rgba.props, function( key, prop ) { - rgba[ prop.idx ] = clamp( red[ prop.idx ], prop ); - }); - return this; - } - - if ( type === "object" ) { - if ( red instanceof color ) { - each( spaces, function( spaceName, space ) { - if ( red[ space.cache ] ) { - inst[ space.cache ] = red[ space.cache ].slice(); - } - }); - } else { - each( spaces, function( spaceName, space ) { - var cache = space.cache; - each( space.props, function( key, prop ) { - - // if the cache doesn't exist, and we know how to convert - if ( !inst[ cache ] && space.to ) { - - // if the value was null, we don't need to copy it - // if the key was alpha, we don't need to copy it either - if ( key === "alpha" || red[ key ] == null ) { - return; - } - inst[ cache ] = space.to( inst._rgba ); - } - - // this is the only case where we allow nulls for ALL properties. - // call clamp with alwaysAllowEmpty - inst[ cache ][ prop.idx ] = clamp( red[ key ], prop, true ); - }); - - // everything defined but alpha? - if ( inst[ cache ] && $.inArray( null, inst[ cache ].slice( 0, 3 ) ) < 0 ) { - // use the default of 1 - inst[ cache ][ 3 ] = 1; - if ( space.from ) { - inst._rgba = space.from( inst[ cache ] ); - } - } - }); - } - return this; - } - }, - is: function( compare ) { - var is = color( compare ), - same = true, - inst = this; - - each( spaces, function( _, space ) { - var localCache, - isCache = is[ space.cache ]; - if (isCache) { - localCache = inst[ space.cache ] || space.to && space.to( inst._rgba ) || []; - each( space.props, function( _, prop ) { - if ( isCache[ prop.idx ] != null ) { - same = ( isCache[ prop.idx ] === localCache[ prop.idx ] ); - return same; - } - }); - } - return same; - }); - return same; - }, - _space: function() { - var used = [], - inst = this; - each( spaces, function( spaceName, space ) { - if ( inst[ space.cache ] ) { - used.push( spaceName ); - } - }); - return used.pop(); - }, - transition: function( other, distance ) { - var end = color( other ), - spaceName = end._space(), - space = spaces[ spaceName ], - startColor = this.alpha() === 0 ? color( "transparent" ) : this, - start = startColor[ space.cache ] || space.to( startColor._rgba ), - result = start.slice(); - - end = end[ space.cache ]; - each( space.props, function( key, prop ) { - var index = prop.idx, - startValue = start[ index ], - endValue = end[ index ], - type = propTypes[ prop.type ] || {}; - - // if null, don't override start value - if ( endValue === null ) { - return; - } - // if null - use end - if ( startValue === null ) { - result[ index ] = endValue; - } else { - if ( type.mod ) { - if ( endValue - startValue > type.mod / 2 ) { - startValue += type.mod; - } else if ( startValue - endValue > type.mod / 2 ) { - startValue -= type.mod; - } - } - result[ index ] = clamp( ( endValue - startValue ) * distance + startValue, prop ); - } - }); - return this[ spaceName ]( result ); - }, - blend: function( opaque ) { - // if we are already opaque - return ourself - if ( this._rgba[ 3 ] === 1 ) { - return this; - } - - var rgb = this._rgba.slice(), - a = rgb.pop(), - blend = color( opaque )._rgba; - - return color( jQuery.map( rgb, function( v, i ) { - return ( 1 - a ) * blend[ i ] + a * v; - })); - }, - toRgbaString: function() { - var prefix = "rgba(", - rgba = jQuery.map( this._rgba, function( v, i ) { - return v == null ? ( i > 2 ? 1 : 0 ) : v; - }); - - if ( rgba[ 3 ] === 1 ) { - rgba.pop(); - prefix = "rgb("; - } - - return prefix + rgba.join() + ")"; - }, - toHslaString: function() { - var prefix = "hsla(", - hsla = jQuery.map( this.hsla(), function( v, i ) { - if ( v == null ) { - v = i > 2 ? 1 : 0; - } - - // catch 1 and 2 - if ( i && i < 3 ) { - v = Math.round( v * 100 ) + "%"; - } - return v; - }); - - if ( hsla[ 3 ] === 1 ) { - hsla.pop(); - prefix = "hsl("; - } - return prefix + hsla.join() + ")"; - }, - toHexString: function( includeAlpha ) { - var rgba = this._rgba.slice(), - alpha = rgba.pop(); - - if ( includeAlpha ) { - rgba.push( ~~( alpha * 255 ) ); - } - - return "#" + jQuery.map( rgba, function( v ) { - - // default to 0 when nulls exist - v = ( v || 0 ).toString( 16 ); - return v.length === 1 ? "0" + v : v; - }).join(""); - }, - toString: function() { - return this._rgba[ 3 ] === 0 ? "transparent" : this.toRgbaString(); - } -}); -color.fn.parse.prototype = color.fn; - -// hsla conversions adapted from: -// https://code.google.com/p/maashaack/source/browse/packages/graphics/trunk/src/graphics/colors/HUE2RGB.as?r=5021 - -function hue2rgb( p, q, h ) { - h = ( h + 1 ) % 1; - if ( h * 6 < 1 ) { - return p + (q - p) * h * 6; - } - if ( h * 2 < 1) { - return q; - } - if ( h * 3 < 2 ) { - return p + (q - p) * ((2/3) - h) * 6; - } - return p; -} - -spaces.hsla.to = function ( rgba ) { - if ( rgba[ 0 ] == null || rgba[ 1 ] == null || rgba[ 2 ] == null ) { - return [ null, null, null, rgba[ 3 ] ]; - } - var r = rgba[ 0 ] / 255, - g = rgba[ 1 ] / 255, - b = rgba[ 2 ] / 255, - a = rgba[ 3 ], - max = Math.max( r, g, b ), - min = Math.min( r, g, b ), - diff = max - min, - add = max + min, - l = add * 0.5, - h, s; - - if ( min === max ) { - h = 0; - } else if ( r === max ) { - h = ( 60 * ( g - b ) / diff ) + 360; - } else if ( g === max ) { - h = ( 60 * ( b - r ) / diff ) + 120; - } else { - h = ( 60 * ( r - g ) / diff ) + 240; - } - - if ( l === 0 || l === 1 ) { - s = l; - } else if ( l <= 0.5 ) { - s = diff / add; - } else { - s = diff / ( 2 - add ); - } - return [ Math.round(h) % 360, s, l, a == null ? 1 : a ]; -}; - -spaces.hsla.from = function ( hsla ) { - if ( hsla[ 0 ] == null || hsla[ 1 ] == null || hsla[ 2 ] == null ) { - return [ null, null, null, hsla[ 3 ] ]; - } - var h = hsla[ 0 ] / 360, - s = hsla[ 1 ], - l = hsla[ 2 ], - a = hsla[ 3 ], - q = l <= 0.5 ? l * ( 1 + s ) : l + s - l * s, - p = 2 * l - q; - - return [ - Math.round( hue2rgb( p, q, h + ( 1 / 3 ) ) * 255 ), - Math.round( hue2rgb( p, q, h ) * 255 ), - Math.round( hue2rgb( p, q, h - ( 1 / 3 ) ) * 255 ), - a - ]; -}; - - -each( spaces, function( spaceName, space ) { - var props = space.props, - cache = space.cache, - to = space.to, - from = space.from; - - // makes rgba() and hsla() - color.fn[ spaceName ] = function( value ) { - - // generate a cache for this space if it doesn't exist - if ( to && !this[ cache ] ) { - this[ cache ] = to( this._rgba ); - } - if ( value === undefined ) { - return this[ cache ].slice(); - } - - var ret, - type = jQuery.type( value ), - arr = ( type === "array" || type === "object" ) ? value : arguments, - local = this[ cache ].slice(); - - each( props, function( key, prop ) { - var val = arr[ type === "object" ? key : prop.idx ]; - if ( val == null ) { - val = local[ prop.idx ]; - } - local[ prop.idx ] = clamp( val, prop ); - }); - - if ( from ) { - ret = color( from( local ) ); - ret[ cache ] = local; - return ret; - } else { - return color( local ); - } - }; - - // makes red() green() blue() alpha() hue() saturation() lightness() - each( props, function( key, prop ) { - // alpha is included in more than one space - if ( color.fn[ key ] ) { - return; - } - color.fn[ key ] = function( value ) { - var vtype = jQuery.type( value ), - fn = ( key === "alpha" ? ( this._hsla ? "hsla" : "rgba" ) : spaceName ), - local = this[ fn ](), - cur = local[ prop.idx ], - match; - - if ( vtype === "undefined" ) { - return cur; - } - - if ( vtype === "function" ) { - value = value.call( this, cur ); - vtype = jQuery.type( value ); - } - if ( value == null && prop.empty ) { - return this; - } - if ( vtype === "string" ) { - match = rplusequals.exec( value ); - if ( match ) { - value = cur + parseFloat( match[ 2 ] ) * ( match[ 1 ] === "+" ? 1 : -1 ); - } - } - local[ prop.idx ] = value; - return this[ fn ]( local ); - }; - }); -}); - -// add .fx.step functions -each( stepHooks, function( i, hook ) { - jQuery.cssHooks[ hook ] = { - set: function( elem, value ) { - var parsed, curElem, - backgroundColor = ""; - - if ( jQuery.type( value ) !== "string" || ( parsed = stringParse( value ) ) ) { - value = color( parsed || value ); - if ( !support.rgba && value._rgba[ 3 ] !== 1 ) { - curElem = hook === "backgroundColor" ? elem.parentNode : elem; - while ( - (backgroundColor === "" || backgroundColor === "transparent") && - curElem && curElem.style - ) { - try { - backgroundColor = jQuery.css( curElem, "backgroundColor" ); - curElem = curElem.parentNode; - } catch ( e ) { - } - } - - value = value.blend( backgroundColor && backgroundColor !== "transparent" ? - backgroundColor : - "_default" ); - } - - value = value.toRgbaString(); - } - try { - elem.style[ hook ] = value; - } catch( error ) { - // wrapped to prevent IE from throwing errors on "invalid" values like 'auto' or 'inherit' - } - } - }; - jQuery.fx.step[ hook ] = function( fx ) { - if ( !fx.colorInit ) { - fx.start = color( fx.elem, hook ); - fx.end = color( fx.end ); - fx.colorInit = true; - } - jQuery.cssHooks[ hook ].set( fx.elem, fx.start.transition( fx.end, fx.pos ) ); - }; -}); - -jQuery.cssHooks.borderColor = { - expand: function( value ) { - var expanded = {}; - - each( [ "Top", "Right", "Bottom", "Left" ], function( i, part ) { - expanded[ "border" + part + "Color" ] = value; - }); - return expanded; - } -}; - -// Basic color names only. -// Usage of any of the other color names requires adding yourself or including -// jquery.color.svg-names.js. -colors = jQuery.Color.names = { - // 4.1. Basic color keywords - aqua: "#00ffff", - black: "#000000", - blue: "#0000ff", - fuchsia: "#ff00ff", - gray: "#808080", - green: "#008000", - lime: "#00ff00", - maroon: "#800000", - navy: "#000080", - olive: "#808000", - purple: "#800080", - red: "#ff0000", - silver: "#c0c0c0", - teal: "#008080", - white: "#ffffff", - yellow: "#ffff00", - - // 4.2.3. "transparent" color keyword - transparent: [ null, null, null, 0 ], - - _default: "#ffffff" -}; - -})( jQuery ); - - - -/******************************************************************************/ -/****************************** CLASS ANIMATIONS ******************************/ -/******************************************************************************/ -(function() { - -var classAnimationActions = [ "add", "remove", "toggle" ], - shorthandStyles = { - border: 1, - borderBottom: 1, - borderColor: 1, - borderLeft: 1, - borderRight: 1, - borderTop: 1, - borderWidth: 1, - margin: 1, - padding: 1 - }; - -$.each([ "borderLeftStyle", "borderRightStyle", "borderBottomStyle", "borderTopStyle" ], function( _, prop ) { - $.fx.step[ prop ] = function( fx ) { - if ( fx.end !== "none" && !fx.setAttr || fx.pos === 1 && !fx.setAttr ) { - jQuery.style( fx.elem, prop, fx.end ); - fx.setAttr = true; - } - }; -}); - -function getElementStyles() { - var style = this.ownerDocument.defaultView ? - this.ownerDocument.defaultView.getComputedStyle( this, null ) : - this.currentStyle, - newStyle = {}, - key, - len; - - // webkit enumerates style porperties - if ( style && style.length && style[ 0 ] && style[ style[ 0 ] ] ) { - len = style.length; - while ( len-- ) { - key = style[ len ]; - if ( typeof style[ key ] === "string" ) { - newStyle[ $.camelCase( key ) ] = style[ key ]; - } - } - } else { - for ( key in style ) { - if ( typeof style[ key ] === "string" ) { - newStyle[ key ] = style[ key ]; - } - } - } - - return newStyle; -} - - -function styleDifference( oldStyle, newStyle ) { - var diff = {}, - name, value; - - for ( name in newStyle ) { - value = newStyle[ name ]; - if ( oldStyle[ name ] !== value ) { - if ( !shorthandStyles[ name ] ) { - if ( $.fx.step[ name ] || !isNaN( parseFloat( value ) ) ) { - diff[ name ] = value; - } - } - } - } - - return diff; -} - -$.effects.animateClass = function( value, duration, easing, callback ) { - var o = $.speed( duration, easing, callback ); - - return this.queue( function() { - var animated = $( this ), - baseClass = animated.attr( "class" ) || "", - applyClassChange, - allAnimations = o.children ? animated.find( "*" ).andSelf() : animated; - - // map the animated objects to store the original styles. - allAnimations = allAnimations.map(function() { - var el = $( this ); - return { - el: el, - start: getElementStyles.call( this ) - }; - }); - - // apply class change - applyClassChange = function() { - $.each( classAnimationActions, function(i, action) { - if ( value[ action ] ) { - animated[ action + "Class" ]( value[ action ] ); - } - }); - }; - applyClassChange(); - - // map all animated objects again - calculate new styles and diff - allAnimations = allAnimations.map(function() { - this.end = getElementStyles.call( this.el[ 0 ] ); - this.diff = styleDifference( this.start, this.end ); - return this; - }); - - // apply original class - animated.attr( "class", baseClass ); - - // map all animated objects again - this time collecting a promise - allAnimations = allAnimations.map(function() { - var styleInfo = this, - dfd = $.Deferred(), - opts = jQuery.extend({}, o, { - queue: false, - complete: function() { - dfd.resolve( styleInfo ); - } - }); - - this.el.animate( this.diff, opts ); - return dfd.promise(); - }); - - // once all animations have completed: - $.when.apply( $, allAnimations.get() ).done(function() { - - // set the final class - applyClassChange(); - - // for each animated element, - // clear all css properties that were animated - $.each( arguments, function() { - var el = this.el; - $.each( this.diff, function(key) { - el.css( key, '' ); - }); - }); - - // this is guarnteed to be there if you use jQuery.speed() - // it also handles dequeuing the next anim... - o.complete.call( animated[ 0 ] ); - }); - }); -}; - -$.fn.extend({ - _addClass: $.fn.addClass, - addClass: function( classNames, speed, easing, callback ) { - return speed ? - $.effects.animateClass.call( this, - { add: classNames }, speed, easing, callback ) : - this._addClass( classNames ); - }, - - _removeClass: $.fn.removeClass, - removeClass: function( classNames, speed, easing, callback ) { - return speed ? - $.effects.animateClass.call( this, - { remove: classNames }, speed, easing, callback ) : - this._removeClass( classNames ); - }, - - _toggleClass: $.fn.toggleClass, - toggleClass: function( classNames, force, speed, easing, callback ) { - if ( typeof force === "boolean" || force === undefined ) { - if ( !speed ) { - // without speed parameter - return this._toggleClass( classNames, force ); - } else { - return $.effects.animateClass.call( this, - (force ? { add: classNames } : { remove: classNames }), - speed, easing, callback ); - } - } else { - // without force parameter - return $.effects.animateClass.call( this, - { toggle: classNames }, force, speed, easing ); - } - }, - - switchClass: function( remove, add, speed, easing, callback) { - return $.effects.animateClass.call( this, { - add: add, - remove: remove - }, speed, easing, callback ); - } -}); - -})(); - -/******************************************************************************/ -/*********************************** EFFECTS **********************************/ -/******************************************************************************/ - -(function() { - -$.extend( $.effects, { - version: "1.9.2", - - // Saves a set of properties in a data storage - save: function( element, set ) { - for( var i=0; i < set.length; i++ ) { - if ( set[ i ] !== null ) { - element.data( dataSpace + set[ i ], element[ 0 ].style[ set[ i ] ] ); - } - } - }, - - // Restores a set of previously saved properties from a data storage - restore: function( element, set ) { - var val, i; - for( i=0; i < set.length; i++ ) { - if ( set[ i ] !== null ) { - val = element.data( dataSpace + set[ i ] ); - // support: jQuery 1.6.2 - // http://bugs.jquery.com/ticket/9917 - // jQuery 1.6.2 incorrectly returns undefined for any falsy value. - // We can't differentiate between "" and 0 here, so we just assume - // empty string since it's likely to be a more common value... - if ( val === undefined ) { - val = ""; - } - element.css( set[ i ], val ); - } - } - }, - - setMode: function( el, mode ) { - if (mode === "toggle") { - mode = el.is( ":hidden" ) ? "show" : "hide"; - } - return mode; - }, - - // Translates a [top,left] array into a baseline value - // this should be a little more flexible in the future to handle a string & hash - getBaseline: function( origin, original ) { - var y, x; - switch ( origin[ 0 ] ) { - case "top": y = 0; break; - case "middle": y = 0.5; break; - case "bottom": y = 1; break; - default: y = origin[ 0 ] / original.height; - } - switch ( origin[ 1 ] ) { - case "left": x = 0; break; - case "center": x = 0.5; break; - case "right": x = 1; break; - default: x = origin[ 1 ] / original.width; - } - return { - x: x, - y: y - }; - }, - - // Wraps the element around a wrapper that copies position properties - createWrapper: function( element ) { - - // if the element is already wrapped, return it - if ( element.parent().is( ".ui-effects-wrapper" )) { - return element.parent(); - } - - // wrap the element - var props = { - width: element.outerWidth(true), - height: element.outerHeight(true), - "float": element.css( "float" ) - }, - wrapper = $( "

" ) - .addClass( "ui-effects-wrapper" ) - .css({ - fontSize: "100%", - background: "transparent", - border: "none", - margin: 0, - padding: 0 - }), - // Store the size in case width/height are defined in % - Fixes #5245 - size = { - width: element.width(), - height: element.height() - }, - active = document.activeElement; - - // support: Firefox - // Firefox incorrectly exposes anonymous content - // https://bugzilla.mozilla.org/show_bug.cgi?id=561664 - try { - active.id; - } catch( e ) { - active = document.body; - } - - element.wrap( wrapper ); - - // Fixes #7595 - Elements lose focus when wrapped. - if ( element[ 0 ] === active || $.contains( element[ 0 ], active ) ) { - $( active ).focus(); - } - - wrapper = element.parent(); //Hotfix for jQuery 1.4 since some change in wrap() seems to actually lose the reference to the wrapped element - - // transfer positioning properties to the wrapper - if ( element.css( "position" ) === "static" ) { - wrapper.css({ position: "relative" }); - element.css({ position: "relative" }); - } else { - $.extend( props, { - position: element.css( "position" ), - zIndex: element.css( "z-index" ) - }); - $.each([ "top", "left", "bottom", "right" ], function(i, pos) { - props[ pos ] = element.css( pos ); - if ( isNaN( parseInt( props[ pos ], 10 ) ) ) { - props[ pos ] = "auto"; - } - }); - element.css({ - position: "relative", - top: 0, - left: 0, - right: "auto", - bottom: "auto" - }); - } - element.css(size); - - return wrapper.css( props ).show(); - }, - - removeWrapper: function( element ) { - var active = document.activeElement; - - if ( element.parent().is( ".ui-effects-wrapper" ) ) { - element.parent().replaceWith( element ); - - // Fixes #7595 - Elements lose focus when wrapped. - if ( element[ 0 ] === active || $.contains( element[ 0 ], active ) ) { - $( active ).focus(); - } - } - - - return element; - }, - - setTransition: function( element, list, factor, value ) { - value = value || {}; - $.each( list, function( i, x ) { - var unit = element.cssUnit( x ); - if ( unit[ 0 ] > 0 ) { - value[ x ] = unit[ 0 ] * factor + unit[ 1 ]; - } - }); - return value; - } -}); - -// return an effect options object for the given parameters: -function _normalizeArguments( effect, options, speed, callback ) { - - // allow passing all options as the first parameter - if ( $.isPlainObject( effect ) ) { - options = effect; - effect = effect.effect; - } - - // convert to an object - effect = { effect: effect }; - - // catch (effect, null, ...) - if ( options == null ) { - options = {}; - } - - // catch (effect, callback) - if ( $.isFunction( options ) ) { - callback = options; - speed = null; - options = {}; - } - - // catch (effect, speed, ?) - if ( typeof options === "number" || $.fx.speeds[ options ] ) { - callback = speed; - speed = options; - options = {}; - } - - // catch (effect, options, callback) - if ( $.isFunction( speed ) ) { - callback = speed; - speed = null; - } - - // add options to effect - if ( options ) { - $.extend( effect, options ); - } - - speed = speed || options.duration; - effect.duration = $.fx.off ? 0 : - typeof speed === "number" ? speed : - speed in $.fx.speeds ? $.fx.speeds[ speed ] : - $.fx.speeds._default; - - effect.complete = callback || options.complete; - - return effect; -} - -function standardSpeed( speed ) { - // valid standard speeds - if ( !speed || typeof speed === "number" || $.fx.speeds[ speed ] ) { - return true; - } - - // invalid strings - treat as "normal" speed - if ( typeof speed === "string" && !$.effects.effect[ speed ] ) { - // TODO: remove in 2.0 (#7115) - if ( backCompat && $.effects[ speed ] ) { - return false; - } - return true; - } - - return false; -} - -$.fn.extend({ - effect: function( /* effect, options, speed, callback */ ) { - var args = _normalizeArguments.apply( this, arguments ), - mode = args.mode, - queue = args.queue, - effectMethod = $.effects.effect[ args.effect ], - - // DEPRECATED: remove in 2.0 (#7115) - oldEffectMethod = !effectMethod && backCompat && $.effects[ args.effect ]; - - if ( $.fx.off || !( effectMethod || oldEffectMethod ) ) { - // delegate to the original method (e.g., .show()) if possible - if ( mode ) { - return this[ mode ]( args.duration, args.complete ); - } else { - return this.each( function() { - if ( args.complete ) { - args.complete.call( this ); - } - }); - } - } - - function run( next ) { - var elem = $( this ), - complete = args.complete, - mode = args.mode; - - function done() { - if ( $.isFunction( complete ) ) { - complete.call( elem[0] ); - } - if ( $.isFunction( next ) ) { - next(); - } - } - - // if the element is hiddden and mode is hide, - // or element is visible and mode is show - if ( elem.is( ":hidden" ) ? mode === "hide" : mode === "show" ) { - done(); - } else { - effectMethod.call( elem[0], args, done ); - } - } - - // TODO: remove this check in 2.0, effectMethod will always be true - if ( effectMethod ) { - return queue === false ? this.each( run ) : this.queue( queue || "fx", run ); - } else { - // DEPRECATED: remove in 2.0 (#7115) - return oldEffectMethod.call(this, { - options: args, - duration: args.duration, - callback: args.complete, - mode: args.mode - }); - } - }, - - _show: $.fn.show, - show: function( speed ) { - if ( standardSpeed( speed ) ) { - return this._show.apply( this, arguments ); - } else { - var args = _normalizeArguments.apply( this, arguments ); - args.mode = "show"; - return this.effect.call( this, args ); - } - }, - - _hide: $.fn.hide, - hide: function( speed ) { - if ( standardSpeed( speed ) ) { - return this._hide.apply( this, arguments ); - } else { - var args = _normalizeArguments.apply( this, arguments ); - args.mode = "hide"; - return this.effect.call( this, args ); - } - }, - - // jQuery core overloads toggle and creates _toggle - __toggle: $.fn.toggle, - toggle: function( speed ) { - if ( standardSpeed( speed ) || typeof speed === "boolean" || $.isFunction( speed ) ) { - return this.__toggle.apply( this, arguments ); - } else { - var args = _normalizeArguments.apply( this, arguments ); - args.mode = "toggle"; - return this.effect.call( this, args ); - } - }, - - // helper functions - cssUnit: function(key) { - var style = this.css( key ), - val = []; - - $.each( [ "em", "px", "%", "pt" ], function( i, unit ) { - if ( style.indexOf( unit ) > 0 ) { - val = [ parseFloat( style ), unit ]; - } - }); - return val; - } -}); - -})(); - -/******************************************************************************/ -/*********************************** EASING ***********************************/ -/******************************************************************************/ - -(function() { - -// based on easing equations from Robert Penner (http://www.robertpenner.com/easing) - -var baseEasings = {}; - -$.each( [ "Quad", "Cubic", "Quart", "Quint", "Expo" ], function( i, name ) { - baseEasings[ name ] = function( p ) { - return Math.pow( p, i + 2 ); - }; -}); - -$.extend( baseEasings, { - Sine: function ( p ) { - return 1 - Math.cos( p * Math.PI / 2 ); - }, - Circ: function ( p ) { - return 1 - Math.sqrt( 1 - p * p ); - }, - Elastic: function( p ) { - return p === 0 || p === 1 ? p : - -Math.pow( 2, 8 * (p - 1) ) * Math.sin( ( (p - 1) * 80 - 7.5 ) * Math.PI / 15 ); - }, - Back: function( p ) { - return p * p * ( 3 * p - 2 ); - }, - Bounce: function ( p ) { - var pow2, - bounce = 4; - - while ( p < ( ( pow2 = Math.pow( 2, --bounce ) ) - 1 ) / 11 ) {} - return 1 / Math.pow( 4, 3 - bounce ) - 7.5625 * Math.pow( ( pow2 * 3 - 2 ) / 22 - p, 2 ); - } -}); - -$.each( baseEasings, function( name, easeIn ) { - $.easing[ "easeIn" + name ] = easeIn; - $.easing[ "easeOut" + name ] = function( p ) { - return 1 - easeIn( 1 - p ); - }; - $.easing[ "easeInOut" + name ] = function( p ) { - return p < 0.5 ? - easeIn( p * 2 ) / 2 : - 1 - easeIn( p * -2 + 2 ) / 2; - }; -}); - -})(); - -})(jQuery)); - -(function( $, undefined ) { - -var uid = 0, - hideProps = {}, - showProps = {}; - -hideProps.height = hideProps.paddingTop = hideProps.paddingBottom = - hideProps.borderTopWidth = hideProps.borderBottomWidth = "hide"; -showProps.height = showProps.paddingTop = showProps.paddingBottom = - showProps.borderTopWidth = showProps.borderBottomWidth = "show"; - -$.widget( "ui.accordion", { - version: "1.9.2", - options: { - active: 0, - animate: {}, - collapsible: false, - event: "click", - header: "> li > :first-child,> :not(li):even", - heightStyle: "auto", - icons: { - activeHeader: "ui-icon-triangle-1-s", - header: "ui-icon-triangle-1-e" - }, - - // callbacks - activate: null, - beforeActivate: null - }, - - _create: function() { - var accordionId = this.accordionId = "ui-accordion-" + - (this.element.attr( "id" ) || ++uid), - options = this.options; - - this.prevShow = this.prevHide = $(); - this.element.addClass( "ui-accordion ui-widget ui-helper-reset" ); - - this.headers = this.element.find( options.header ) - .addClass( "ui-accordion-header ui-helper-reset ui-state-default ui-corner-all" ); - this._hoverable( this.headers ); - this._focusable( this.headers ); - - this.headers.next() - .addClass( "ui-accordion-content ui-helper-reset ui-widget-content ui-corner-bottom" ) - .hide(); - - // don't allow collapsible: false and active: false / null - if ( !options.collapsible && (options.active === false || options.active == null) ) { - options.active = 0; - } - // handle negative values - if ( options.active < 0 ) { - options.active += this.headers.length; - } - this.active = this._findActive( options.active ) - .addClass( "ui-accordion-header-active ui-state-active" ) - .toggleClass( "ui-corner-all ui-corner-top" ); - this.active.next() - .addClass( "ui-accordion-content-active" ) - .show(); - - this._createIcons(); - this.refresh(); - - // ARIA - this.element.attr( "role", "tablist" ); - - this.headers - .attr( "role", "tab" ) - .each(function( i ) { - var header = $( this ), - headerId = header.attr( "id" ), - panel = header.next(), - panelId = panel.attr( "id" ); - if ( !headerId ) { - headerId = accordionId + "-header-" + i; - header.attr( "id", headerId ); - } - if ( !panelId ) { - panelId = accordionId + "-panel-" + i; - panel.attr( "id", panelId ); - } - header.attr( "aria-controls", panelId ); - panel.attr( "aria-labelledby", headerId ); - }) - .next() - .attr( "role", "tabpanel" ); - - this.headers - .not( this.active ) - .attr({ - "aria-selected": "false", - tabIndex: -1 - }) - .next() - .attr({ - "aria-expanded": "false", - "aria-hidden": "true" - }) - .hide(); - - // make sure at least one header is in the tab order - if ( !this.active.length ) { - this.headers.eq( 0 ).attr( "tabIndex", 0 ); - } else { - this.active.attr({ - "aria-selected": "true", - tabIndex: 0 - }) - .next() - .attr({ - "aria-expanded": "true", - "aria-hidden": "false" - }); - } - - this._on( this.headers, { keydown: "_keydown" }); - this._on( this.headers.next(), { keydown: "_panelKeyDown" }); - this._setupEvents( options.event ); - }, - - _getCreateEventData: function() { - return { - header: this.active, - content: !this.active.length ? $() : this.active.next() - }; - }, - - _createIcons: function() { - var icons = this.options.icons; - if ( icons ) { - $( "" ) - .addClass( "ui-accordion-header-icon ui-icon " + icons.header ) - .prependTo( this.headers ); - this.active.children( ".ui-accordion-header-icon" ) - .removeClass( icons.header ) - .addClass( icons.activeHeader ); - this.headers.addClass( "ui-accordion-icons" ); - } - }, - - _destroyIcons: function() { - this.headers - .removeClass( "ui-accordion-icons" ) - .children( ".ui-accordion-header-icon" ) - .remove(); - }, - - _destroy: function() { - var contents; - - // clean up main element - this.element - .removeClass( "ui-accordion ui-widget ui-helper-reset" ) - .removeAttr( "role" ); - - // clean up headers - this.headers - .removeClass( "ui-accordion-header ui-accordion-header-active ui-helper-reset ui-state-default ui-corner-all ui-state-active ui-state-disabled ui-corner-top" ) - .removeAttr( "role" ) - .removeAttr( "aria-selected" ) - .removeAttr( "aria-controls" ) - .removeAttr( "tabIndex" ) - .each(function() { - if ( /^ui-accordion/.test( this.id ) ) { - this.removeAttribute( "id" ); - } - }); - this._destroyIcons(); - - // clean up content panels - contents = this.headers.next() - .css( "display", "" ) - .removeAttr( "role" ) - .removeAttr( "aria-expanded" ) - .removeAttr( "aria-hidden" ) - .removeAttr( "aria-labelledby" ) - .removeClass( "ui-helper-reset ui-widget-content ui-corner-bottom ui-accordion-content ui-accordion-content-active ui-state-disabled" ) - .each(function() { - if ( /^ui-accordion/.test( this.id ) ) { - this.removeAttribute( "id" ); - } - }); - if ( this.options.heightStyle !== "content" ) { - contents.css( "height", "" ); - } - }, - - _setOption: function( key, value ) { - if ( key === "active" ) { - // _activate() will handle invalid values and update this.options - this._activate( value ); - return; - } - - if ( key === "event" ) { - if ( this.options.event ) { - this._off( this.headers, this.options.event ); - } - this._setupEvents( value ); - } - - this._super( key, value ); - - // setting collapsible: false while collapsed; open first panel - if ( key === "collapsible" && !value && this.options.active === false ) { - this._activate( 0 ); - } - - if ( key === "icons" ) { - this._destroyIcons(); - if ( value ) { - this._createIcons(); - } - } - - // #5332 - opacity doesn't cascade to positioned elements in IE - // so we need to add the disabled class to the headers and panels - if ( key === "disabled" ) { - this.headers.add( this.headers.next() ) - .toggleClass( "ui-state-disabled", !!value ); - } - }, - - _keydown: function( event ) { - if ( event.altKey || event.ctrlKey ) { - return; - } - - var keyCode = $.ui.keyCode, - length = this.headers.length, - currentIndex = this.headers.index( event.target ), - toFocus = false; - - switch ( event.keyCode ) { - case keyCode.RIGHT: - case keyCode.DOWN: - toFocus = this.headers[ ( currentIndex + 1 ) % length ]; - break; - case keyCode.LEFT: - case keyCode.UP: - toFocus = this.headers[ ( currentIndex - 1 + length ) % length ]; - break; - case keyCode.SPACE: - case keyCode.ENTER: - this._eventHandler( event ); - break; - case keyCode.HOME: - toFocus = this.headers[ 0 ]; - break; - case keyCode.END: - toFocus = this.headers[ length - 1 ]; - break; - } - - if ( toFocus ) { - $( event.target ).attr( "tabIndex", -1 ); - $( toFocus ).attr( "tabIndex", 0 ); - toFocus.focus(); - event.preventDefault(); - } - }, - - _panelKeyDown : function( event ) { - if ( event.keyCode === $.ui.keyCode.UP && event.ctrlKey ) { - $( event.currentTarget ).prev().focus(); - } - }, - - refresh: function() { - var maxHeight, overflow, - heightStyle = this.options.heightStyle, - parent = this.element.parent(); - - - if ( heightStyle === "fill" ) { - // IE 6 treats height like minHeight, so we need to turn off overflow - // in order to get a reliable height - // we use the minHeight support test because we assume that only - // browsers that don't support minHeight will treat height as minHeight - if ( !$.support.minHeight ) { - overflow = parent.css( "overflow" ); - parent.css( "overflow", "hidden"); - } - maxHeight = parent.height(); - this.element.siblings( ":visible" ).each(function() { - var elem = $( this ), - position = elem.css( "position" ); - - if ( position === "absolute" || position === "fixed" ) { - return; - } - maxHeight -= elem.outerHeight( true ); - }); - if ( overflow ) { - parent.css( "overflow", overflow ); - } - - this.headers.each(function() { - maxHeight -= $( this ).outerHeight( true ); - }); - - this.headers.next() - .each(function() { - $( this ).height( Math.max( 0, maxHeight - - $( this ).innerHeight() + $( this ).height() ) ); - }) - .css( "overflow", "auto" ); - } else if ( heightStyle === "auto" ) { - maxHeight = 0; - this.headers.next() - .each(function() { - maxHeight = Math.max( maxHeight, $( this ).css( "height", "" ).height() ); - }) - .height( maxHeight ); - } - }, - - _activate: function( index ) { - var active = this._findActive( index )[ 0 ]; - - // trying to activate the already active panel - if ( active === this.active[ 0 ] ) { - return; - } - - // trying to collapse, simulate a click on the currently active header - active = active || this.active[ 0 ]; - - this._eventHandler({ - target: active, - currentTarget: active, - preventDefault: $.noop - }); - }, - - _findActive: function( selector ) { - return typeof selector === "number" ? this.headers.eq( selector ) : $(); - }, - - _setupEvents: function( event ) { - var events = {}; - if ( !event ) { - return; - } - $.each( event.split(" "), function( index, eventName ) { - events[ eventName ] = "_eventHandler"; - }); - this._on( this.headers, events ); - }, - - _eventHandler: function( event ) { - var options = this.options, - active = this.active, - clicked = $( event.currentTarget ), - clickedIsActive = clicked[ 0 ] === active[ 0 ], - collapsing = clickedIsActive && options.collapsible, - toShow = collapsing ? $() : clicked.next(), - toHide = active.next(), - eventData = { - oldHeader: active, - oldPanel: toHide, - newHeader: collapsing ? $() : clicked, - newPanel: toShow - }; - - event.preventDefault(); - - if ( - // click on active header, but not collapsible - ( clickedIsActive && !options.collapsible ) || - // allow canceling activation - ( this._trigger( "beforeActivate", event, eventData ) === false ) ) { - return; - } - - options.active = collapsing ? false : this.headers.index( clicked ); - - // when the call to ._toggle() comes after the class changes - // it causes a very odd bug in IE 8 (see #6720) - this.active = clickedIsActive ? $() : clicked; - this._toggle( eventData ); - - // switch classes - // corner classes on the previously active header stay after the animation - active.removeClass( "ui-accordion-header-active ui-state-active" ); - if ( options.icons ) { - active.children( ".ui-accordion-header-icon" ) - .removeClass( options.icons.activeHeader ) - .addClass( options.icons.header ); - } - - if ( !clickedIsActive ) { - clicked - .removeClass( "ui-corner-all" ) - .addClass( "ui-accordion-header-active ui-state-active ui-corner-top" ); - if ( options.icons ) { - clicked.children( ".ui-accordion-header-icon" ) - .removeClass( options.icons.header ) - .addClass( options.icons.activeHeader ); - } - - clicked - .next() - .addClass( "ui-accordion-content-active" ); - } - }, - - _toggle: function( data ) { - var toShow = data.newPanel, - toHide = this.prevShow.length ? this.prevShow : data.oldPanel; - - // handle activating a panel during the animation for another activation - this.prevShow.add( this.prevHide ).stop( true, true ); - this.prevShow = toShow; - this.prevHide = toHide; - - if ( this.options.animate ) { - this._animate( toShow, toHide, data ); - } else { - toHide.hide(); - toShow.show(); - this._toggleComplete( data ); - } - - toHide.attr({ - "aria-expanded": "false", - "aria-hidden": "true" - }); - toHide.prev().attr( "aria-selected", "false" ); - // if we're switching panels, remove the old header from the tab order - // if we're opening from collapsed state, remove the previous header from the tab order - // if we're collapsing, then keep the collapsing header in the tab order - if ( toShow.length && toHide.length ) { - toHide.prev().attr( "tabIndex", -1 ); - } else if ( toShow.length ) { - this.headers.filter(function() { - return $( this ).attr( "tabIndex" ) === 0; - }) - .attr( "tabIndex", -1 ); - } - - toShow - .attr({ - "aria-expanded": "true", - "aria-hidden": "false" - }) - .prev() - .attr({ - "aria-selected": "true", - tabIndex: 0 - }); - }, - - _animate: function( toShow, toHide, data ) { - var total, easing, duration, - that = this, - adjust = 0, - down = toShow.length && - ( !toHide.length || ( toShow.index() < toHide.index() ) ), - animate = this.options.animate || {}, - options = down && animate.down || animate, - complete = function() { - that._toggleComplete( data ); - }; - - if ( typeof options === "number" ) { - duration = options; - } - if ( typeof options === "string" ) { - easing = options; - } - // fall back from options to animation in case of partial down settings - easing = easing || options.easing || animate.easing; - duration = duration || options.duration || animate.duration; - - if ( !toHide.length ) { - return toShow.animate( showProps, duration, easing, complete ); - } - if ( !toShow.length ) { - return toHide.animate( hideProps, duration, easing, complete ); - } - - total = toShow.show().outerHeight(); - toHide.animate( hideProps, { - duration: duration, - easing: easing, - step: function( now, fx ) { - fx.now = Math.round( now ); - } - }); - toShow - .hide() - .animate( showProps, { - duration: duration, - easing: easing, - complete: complete, - step: function( now, fx ) { - fx.now = Math.round( now ); - if ( fx.prop !== "height" ) { - adjust += fx.now; - } else if ( that.options.heightStyle !== "content" ) { - fx.now = Math.round( total - toHide.outerHeight() - adjust ); - adjust = 0; - } - } - }); - }, - - _toggleComplete: function( data ) { - var toHide = data.oldPanel; - - toHide - .removeClass( "ui-accordion-content-active" ) - .prev() - .removeClass( "ui-corner-top" ) - .addClass( "ui-corner-all" ); - - // Work around for rendering bug in IE (#5421) - if ( toHide.length ) { - toHide.parent()[0].className = toHide.parent()[0].className; - } - - this._trigger( "activate", null, data ); - } -}); - - - -// DEPRECATED -if ( $.uiBackCompat !== false ) { - // navigation options - (function( $, prototype ) { - $.extend( prototype.options, { - navigation: false, - navigationFilter: function() { - return this.href.toLowerCase() === location.href.toLowerCase(); - } - }); - - var _create = prototype._create; - prototype._create = function() { - if ( this.options.navigation ) { - var that = this, - headers = this.element.find( this.options.header ), - content = headers.next(), - current = headers.add( content ) - .find( "a" ) - .filter( this.options.navigationFilter ) - [ 0 ]; - if ( current ) { - headers.add( content ).each( function( index ) { - if ( $.contains( this, current ) ) { - that.options.active = Math.floor( index / 2 ); - return false; - } - }); - } - } - _create.call( this ); - }; - }( jQuery, jQuery.ui.accordion.prototype ) ); - - // height options - (function( $, prototype ) { - $.extend( prototype.options, { - heightStyle: null, // remove default so we fall back to old values - autoHeight: true, // use heightStyle: "auto" - clearStyle: false, // use heightStyle: "content" - fillSpace: false // use heightStyle: "fill" - }); - - var _create = prototype._create, - _setOption = prototype._setOption; - - $.extend( prototype, { - _create: function() { - this.options.heightStyle = this.options.heightStyle || - this._mergeHeightStyle(); - - _create.call( this ); - }, - - _setOption: function( key ) { - if ( key === "autoHeight" || key === "clearStyle" || key === "fillSpace" ) { - this.options.heightStyle = this._mergeHeightStyle(); - } - _setOption.apply( this, arguments ); - }, - - _mergeHeightStyle: function() { - var options = this.options; - - if ( options.fillSpace ) { - return "fill"; - } - - if ( options.clearStyle ) { - return "content"; - } - - if ( options.autoHeight ) { - return "auto"; - } - } - }); - }( jQuery, jQuery.ui.accordion.prototype ) ); - - // icon options - (function( $, prototype ) { - $.extend( prototype.options.icons, { - activeHeader: null, // remove default so we fall back to old values - headerSelected: "ui-icon-triangle-1-s" - }); - - var _createIcons = prototype._createIcons; - prototype._createIcons = function() { - if ( this.options.icons ) { - this.options.icons.activeHeader = this.options.icons.activeHeader || - this.options.icons.headerSelected; - } - _createIcons.call( this ); - }; - }( jQuery, jQuery.ui.accordion.prototype ) ); - - // expanded active option, activate method - (function( $, prototype ) { - prototype.activate = prototype._activate; - - var _findActive = prototype._findActive; - prototype._findActive = function( index ) { - if ( index === -1 ) { - index = false; - } - if ( index && typeof index !== "number" ) { - index = this.headers.index( this.headers.filter( index ) ); - if ( index === -1 ) { - index = false; - } - } - return _findActive.call( this, index ); - }; - }( jQuery, jQuery.ui.accordion.prototype ) ); - - // resize method - jQuery.ui.accordion.prototype.resize = jQuery.ui.accordion.prototype.refresh; - - // change events - (function( $, prototype ) { - $.extend( prototype.options, { - change: null, - changestart: null - }); - - var _trigger = prototype._trigger; - prototype._trigger = function( type, event, data ) { - var ret = _trigger.apply( this, arguments ); - if ( !ret ) { - return false; - } - - if ( type === "beforeActivate" ) { - ret = _trigger.call( this, "changestart", event, { - oldHeader: data.oldHeader, - oldContent: data.oldPanel, - newHeader: data.newHeader, - newContent: data.newPanel - }); - } else if ( type === "activate" ) { - ret = _trigger.call( this, "change", event, { - oldHeader: data.oldHeader, - oldContent: data.oldPanel, - newHeader: data.newHeader, - newContent: data.newPanel - }); - } - return ret; - }; - }( jQuery, jQuery.ui.accordion.prototype ) ); - - // animated option - // NOTE: this only provides support for "slide", "bounceslide", and easings - // not the full $.ui.accordion.animations API - (function( $, prototype ) { - $.extend( prototype.options, { - animate: null, - animated: "slide" - }); - - var _create = prototype._create; - prototype._create = function() { - var options = this.options; - if ( options.animate === null ) { - if ( !options.animated ) { - options.animate = false; - } else if ( options.animated === "slide" ) { - options.animate = 300; - } else if ( options.animated === "bounceslide" ) { - options.animate = { - duration: 200, - down: { - easing: "easeOutBounce", - duration: 1000 - } - }; - } else { - options.animate = options.animated; - } - } - - _create.call( this ); - }; - }( jQuery, jQuery.ui.accordion.prototype ) ); -} - -})( jQuery ); - -(function( $, undefined ) { - -// used to prevent race conditions with remote data sources -var requestIndex = 0; - -$.widget( "ui.autocomplete", { - version: "1.9.2", - defaultElement: "", - options: { - appendTo: "body", - autoFocus: false, - delay: 300, - minLength: 1, - position: { - my: "left top", - at: "left bottom", - collision: "none" - }, - source: null, - - // callbacks - change: null, - close: null, - focus: null, - open: null, - response: null, - search: null, - select: null - }, - - pending: 0, - - _create: function() { - // Some browsers only repeat keydown events, not keypress events, - // so we use the suppressKeyPress flag to determine if we've already - // handled the keydown event. #7269 - // Unfortunately the code for & in keypress is the same as the up arrow, - // so we use the suppressKeyPressRepeat flag to avoid handling keypress - // events when we know the keydown event was used to modify the - // search term. #7799 - var suppressKeyPress, suppressKeyPressRepeat, suppressInput; - - this.isMultiLine = this._isMultiLine(); - this.valueMethod = this.element[ this.element.is( "input,textarea" ) ? "val" : "text" ]; - this.isNewMenu = true; - - this.element - .addClass( "ui-autocomplete-input" ) - .attr( "autocomplete", "off" ); - - this._on( this.element, { - keydown: function( event ) { - if ( this.element.prop( "readOnly" ) ) { - suppressKeyPress = true; - suppressInput = true; - suppressKeyPressRepeat = true; - return; - } - - suppressKeyPress = false; - suppressInput = false; - suppressKeyPressRepeat = false; - var keyCode = $.ui.keyCode; - switch( event.keyCode ) { - case keyCode.PAGE_UP: - suppressKeyPress = true; - this._move( "previousPage", event ); - break; - case keyCode.PAGE_DOWN: - suppressKeyPress = true; - this._move( "nextPage", event ); - break; - case keyCode.UP: - suppressKeyPress = true; - this._keyEvent( "previous", event ); - break; - case keyCode.DOWN: - suppressKeyPress = true; - this._keyEvent( "next", event ); - break; - case keyCode.ENTER: - case keyCode.NUMPAD_ENTER: - // when menu is open and has focus - if ( this.menu.active ) { - // #6055 - Opera still allows the keypress to occur - // which causes forms to submit - suppressKeyPress = true; - event.preventDefault(); - this.menu.select( event ); - } - break; - case keyCode.TAB: - if ( this.menu.active ) { - this.menu.select( event ); - } - break; - case keyCode.ESCAPE: - if ( this.menu.element.is( ":visible" ) ) { - this._value( this.term ); - this.close( event ); - // Different browsers have different default behavior for escape - // Single press can mean undo or clear - // Double press in IE means clear the whole form - event.preventDefault(); - } - break; - default: - suppressKeyPressRepeat = true; - // search timeout should be triggered before the input value is changed - this._searchTimeout( event ); - break; - } - }, - keypress: function( event ) { - if ( suppressKeyPress ) { - suppressKeyPress = false; - event.preventDefault(); - return; - } - if ( suppressKeyPressRepeat ) { - return; - } - - // replicate some key handlers to allow them to repeat in Firefox and Opera - var keyCode = $.ui.keyCode; - switch( event.keyCode ) { - case keyCode.PAGE_UP: - this._move( "previousPage", event ); - break; - case keyCode.PAGE_DOWN: - this._move( "nextPage", event ); - break; - case keyCode.UP: - this._keyEvent( "previous", event ); - break; - case keyCode.DOWN: - this._keyEvent( "next", event ); - break; - } - }, - input: function( event ) { - if ( suppressInput ) { - suppressInput = false; - event.preventDefault(); - return; - } - this._searchTimeout( event ); - }, - focus: function() { - this.selectedItem = null; - this.previous = this._value(); - }, - blur: function( event ) { - if ( this.cancelBlur ) { - delete this.cancelBlur; - return; - } - - clearTimeout( this.searching ); - this.close( event ); - this._change( event ); - } - }); - - this._initSource(); - this.menu = $( "
' + - ''; - var thead = (showWeek ? '' : ''); - for (var dow = 0; dow < 7; dow++) { // days of the week - var day = (dow + firstDay) % 7; - thead += '= 5 ? ' class="ui-datepicker-week-end"' : '') + '>' + - '' + dayNamesMin[day] + ''; - } - calender += thead + ''; - var daysInMonth = this._getDaysInMonth(drawYear, drawMonth); - if (drawYear == inst.selectedYear && drawMonth == inst.selectedMonth) - inst.selectedDay = Math.min(inst.selectedDay, daysInMonth); - var leadDays = (this._getFirstDayOfMonth(drawYear, drawMonth) - firstDay + 7) % 7; - var curRows = Math.ceil((leadDays + daysInMonth) / 7); // calculate the number of rows to generate - var numRows = (isMultiMonth ? this.maxRows > curRows ? this.maxRows : curRows : curRows); //If multiple months, use the higher number of rows (see #7043) - this.maxRows = numRows; - var printDate = this._daylightSavingAdjust(new Date(drawYear, drawMonth, 1 - leadDays)); - for (var dRow = 0; dRow < numRows; dRow++) { // create date picker rows - calender += ''; - var tbody = (!showWeek ? '' : ''); - for (var dow = 0; dow < 7; dow++) { // create date picker days - var daySettings = (beforeShowDay ? - beforeShowDay.apply((inst.input ? inst.input[0] : null), [printDate]) : [true, '']); - var otherMonth = (printDate.getMonth() != drawMonth); - var unselectable = (otherMonth && !selectOtherMonths) || !daySettings[0] || - (minDate && printDate < minDate) || (maxDate && printDate > maxDate); - tbody += ''; // display selectable date - printDate.setDate(printDate.getDate() + 1); - printDate = this._daylightSavingAdjust(printDate); - } - calender += tbody + ''; - } - drawMonth++; - if (drawMonth > 11) { - drawMonth = 0; - drawYear++; - } - calender += '
' + this._get(inst, 'weekHeader') + '
' + - this._get(inst, 'calculateWeek')(printDate) + '' + // actions - (otherMonth && !showOtherMonths ? ' ' : // display for other months - (unselectable ? '' + printDate.getDate() + '' : '' + printDate.getDate() + '')) + '
' + (isMultiMonth ? '' + - ((numMonths[0] > 0 && col == numMonths[1]-1) ? '
' : '') : ''); - group += calender; - } - html += group; - } - html += buttonPanel + ($.ui.ie6 && !inst.inline ? - '' : ''); - inst._keyEvent = false; - return html; - }, - - /* Generate the month and year header. */ - _generateMonthYearHeader: function(inst, drawMonth, drawYear, minDate, maxDate, - secondary, monthNames, monthNamesShort) { - var changeMonth = this._get(inst, 'changeMonth'); - var changeYear = this._get(inst, 'changeYear'); - var showMonthAfterYear = this._get(inst, 'showMonthAfterYear'); - var html = '
'; - var monthHtml = ''; - // month selection - if (secondary || !changeMonth) - monthHtml += '' + monthNames[drawMonth] + ''; - else { - var inMinYear = (minDate && minDate.getFullYear() == drawYear); - var inMaxYear = (maxDate && maxDate.getFullYear() == drawYear); - monthHtml += ''; - } - if (!showMonthAfterYear) - html += monthHtml + (secondary || !(changeMonth && changeYear) ? ' ' : ''); - // year selection - if ( !inst.yearshtml ) { - inst.yearshtml = ''; - if (secondary || !changeYear) - html += '' + drawYear + ''; - else { - // determine range of years to display - var years = this._get(inst, 'yearRange').split(':'); - var thisYear = new Date().getFullYear(); - var determineYear = function(value) { - var year = (value.match(/c[+-].*/) ? drawYear + parseInt(value.substring(1), 10) : - (value.match(/[+-].*/) ? thisYear + parseInt(value, 10) : - parseInt(value, 10))); - return (isNaN(year) ? thisYear : year); - }; - var year = determineYear(years[0]); - var endYear = Math.max(year, determineYear(years[1] || '')); - year = (minDate ? Math.max(year, minDate.getFullYear()) : year); - endYear = (maxDate ? Math.min(endYear, maxDate.getFullYear()) : endYear); - inst.yearshtml += ''; - - html += inst.yearshtml; - inst.yearshtml = null; - } - } - html += this._get(inst, 'yearSuffix'); - if (showMonthAfterYear) - html += (secondary || !(changeMonth && changeYear) ? ' ' : '') + monthHtml; - html += '
'; // Close datepicker_header - return html; - }, - - /* Adjust one of the date sub-fields. */ - _adjustInstDate: function(inst, offset, period) { - var year = inst.drawYear + (period == 'Y' ? offset : 0); - var month = inst.drawMonth + (period == 'M' ? offset : 0); - var day = Math.min(inst.selectedDay, this._getDaysInMonth(year, month)) + - (period == 'D' ? offset : 0); - var date = this._restrictMinMax(inst, - this._daylightSavingAdjust(new Date(year, month, day))); - inst.selectedDay = date.getDate(); - inst.drawMonth = inst.selectedMonth = date.getMonth(); - inst.drawYear = inst.selectedYear = date.getFullYear(); - if (period == 'M' || period == 'Y') - this._notifyChange(inst); - }, - - /* Ensure a date is within any min/max bounds. */ - _restrictMinMax: function(inst, date) { - var minDate = this._getMinMaxDate(inst, 'min'); - var maxDate = this._getMinMaxDate(inst, 'max'); - var newDate = (minDate && date < minDate ? minDate : date); - newDate = (maxDate && newDate > maxDate ? maxDate : newDate); - return newDate; - }, - - /* Notify change of month/year. */ - _notifyChange: function(inst) { - var onChange = this._get(inst, 'onChangeMonthYear'); - if (onChange) - onChange.apply((inst.input ? inst.input[0] : null), - [inst.selectedYear, inst.selectedMonth + 1, inst]); - }, - - /* Determine the number of months to show. */ - _getNumberOfMonths: function(inst) { - var numMonths = this._get(inst, 'numberOfMonths'); - return (numMonths == null ? [1, 1] : (typeof numMonths == 'number' ? [1, numMonths] : numMonths)); - }, - - /* Determine the current maximum date - ensure no time components are set. */ - _getMinMaxDate: function(inst, minMax) { - return this._determineDate(inst, this._get(inst, minMax + 'Date'), null); - }, - - /* Find the number of days in a given month. */ - _getDaysInMonth: function(year, month) { - return 32 - this._daylightSavingAdjust(new Date(year, month, 32)).getDate(); - }, - - /* Find the day of the week of the first of a month. */ - _getFirstDayOfMonth: function(year, month) { - return new Date(year, month, 1).getDay(); - }, - - /* Determines if we should allow a "next/prev" month display change. */ - _canAdjustMonth: function(inst, offset, curYear, curMonth) { - var numMonths = this._getNumberOfMonths(inst); - var date = this._daylightSavingAdjust(new Date(curYear, - curMonth + (offset < 0 ? offset : numMonths[0] * numMonths[1]), 1)); - if (offset < 0) - date.setDate(this._getDaysInMonth(date.getFullYear(), date.getMonth())); - return this._isInRange(inst, date); - }, - - /* Is the given date in the accepted range? */ - _isInRange: function(inst, date) { - var minDate = this._getMinMaxDate(inst, 'min'); - var maxDate = this._getMinMaxDate(inst, 'max'); - return ((!minDate || date.getTime() >= minDate.getTime()) && - (!maxDate || date.getTime() <= maxDate.getTime())); - }, - - /* Provide the configuration settings for formatting/parsing. */ - _getFormatConfig: function(inst) { - var shortYearCutoff = this._get(inst, 'shortYearCutoff'); - shortYearCutoff = (typeof shortYearCutoff != 'string' ? shortYearCutoff : - new Date().getFullYear() % 100 + parseInt(shortYearCutoff, 10)); - return {shortYearCutoff: shortYearCutoff, - dayNamesShort: this._get(inst, 'dayNamesShort'), dayNames: this._get(inst, 'dayNames'), - monthNamesShort: this._get(inst, 'monthNamesShort'), monthNames: this._get(inst, 'monthNames')}; - }, - - /* Format the given date for display. */ - _formatDate: function(inst, day, month, year) { - if (!day) { - inst.currentDay = inst.selectedDay; - inst.currentMonth = inst.selectedMonth; - inst.currentYear = inst.selectedYear; - } - var date = (day ? (typeof day == 'object' ? day : - this._daylightSavingAdjust(new Date(year, month, day))) : - this._daylightSavingAdjust(new Date(inst.currentYear, inst.currentMonth, inst.currentDay))); - return this.formatDate(this._get(inst, 'dateFormat'), date, this._getFormatConfig(inst)); - } -}); - -/* - * Bind hover events for datepicker elements. - * Done via delegate so the binding only occurs once in the lifetime of the parent div. - * Global instActive, set by _updateDatepicker allows the handlers to find their way back to the active picker. - */ -function bindHover(dpDiv) { - var selector = 'button, .ui-datepicker-prev, .ui-datepicker-next, .ui-datepicker-calendar td a'; - return dpDiv.delegate(selector, 'mouseout', function() { - $(this).removeClass('ui-state-hover'); - if (this.className.indexOf('ui-datepicker-prev') != -1) $(this).removeClass('ui-datepicker-prev-hover'); - if (this.className.indexOf('ui-datepicker-next') != -1) $(this).removeClass('ui-datepicker-next-hover'); - }) - .delegate(selector, 'mouseover', function(){ - if (!$.datepicker._isDisabledDatepicker( instActive.inline ? dpDiv.parent()[0] : instActive.input[0])) { - $(this).parents('.ui-datepicker-calendar').find('a').removeClass('ui-state-hover'); - $(this).addClass('ui-state-hover'); - if (this.className.indexOf('ui-datepicker-prev') != -1) $(this).addClass('ui-datepicker-prev-hover'); - if (this.className.indexOf('ui-datepicker-next') != -1) $(this).addClass('ui-datepicker-next-hover'); - } - }); -} - -/* jQuery extend now ignores nulls! */ -function extendRemove(target, props) { - $.extend(target, props); - for (var name in props) - if (props[name] == null || props[name] == undefined) - target[name] = props[name]; - return target; -}; - -/* Invoke the datepicker functionality. - @param options string - a command, optionally followed by additional parameters or - Object - settings for attaching new datepicker functionality - @return jQuery object */ -$.fn.datepicker = function(options){ - - /* Verify an empty collection wasn't passed - Fixes #6976 */ - if ( !this.length ) { - return this; - } - - /* Initialise the date picker. */ - if (!$.datepicker.initialized) { - $(document).mousedown($.datepicker._checkExternalClick). - find(document.body).append($.datepicker.dpDiv); - $.datepicker.initialized = true; - } - - var otherArgs = Array.prototype.slice.call(arguments, 1); - if (typeof options == 'string' && (options == 'isDisabled' || options == 'getDate' || options == 'widget')) - return $.datepicker['_' + options + 'Datepicker']. - apply($.datepicker, [this[0]].concat(otherArgs)); - if (options == 'option' && arguments.length == 2 && typeof arguments[1] == 'string') - return $.datepicker['_' + options + 'Datepicker']. - apply($.datepicker, [this[0]].concat(otherArgs)); - return this.each(function() { - typeof options == 'string' ? - $.datepicker['_' + options + 'Datepicker']. - apply($.datepicker, [this].concat(otherArgs)) : - $.datepicker._attachDatepicker(this, options); - }); -}; - -$.datepicker = new Datepicker(); // singleton instance -$.datepicker.initialized = false; -$.datepicker.uuid = new Date().getTime(); -$.datepicker.version = "1.9.2"; - -// Workaround for #4055 -// Add another global to avoid noConflict issues with inline event handlers -window['DP_jQuery_' + dpuuid] = $; - -})(jQuery); - -(function( $, undefined ) { - -var uiDialogClasses = "ui-dialog ui-widget ui-widget-content ui-corner-all ", - sizeRelatedOptions = { - buttons: true, - height: true, - maxHeight: true, - maxWidth: true, - minHeight: true, - minWidth: true, - width: true - }, - resizableRelatedOptions = { - maxHeight: true, - maxWidth: true, - minHeight: true, - minWidth: true - }; - -$.widget("ui.dialog", { - version: "1.9.2", - options: { - autoOpen: true, - buttons: {}, - closeOnEscape: true, - closeText: "close", - dialogClass: "", - draggable: true, - hide: null, - height: "auto", - maxHeight: false, - maxWidth: false, - minHeight: 150, - minWidth: 150, - modal: false, - position: { - my: "center", - at: "center", - of: window, - collision: "fit", - // ensure that the titlebar is never outside the document - using: function( pos ) { - var topOffset = $( this ).css( pos ).offset().top; - if ( topOffset < 0 ) { - $( this ).css( "top", pos.top - topOffset ); - } - } - }, - resizable: true, - show: null, - stack: true, - title: "", - width: 300, - zIndex: 1000 - }, - - _create: function() { - this.originalTitle = this.element.attr( "title" ); - // #5742 - .attr() might return a DOMElement - if ( typeof this.originalTitle !== "string" ) { - this.originalTitle = ""; - } - this.oldPosition = { - parent: this.element.parent(), - index: this.element.parent().children().index( this.element ) - }; - this.options.title = this.options.title || this.originalTitle; - var that = this, - options = this.options, - - title = options.title || " ", - uiDialog, - uiDialogTitlebar, - uiDialogTitlebarClose, - uiDialogTitle, - uiDialogButtonPane; - - uiDialog = ( this.uiDialog = $( "
" ) ) - .addClass( uiDialogClasses + options.dialogClass ) - .css({ - display: "none", - outline: 0, // TODO: move to stylesheet - zIndex: options.zIndex - }) - // setting tabIndex makes the div focusable - .attr( "tabIndex", -1) - .keydown(function( event ) { - if ( options.closeOnEscape && !event.isDefaultPrevented() && event.keyCode && - event.keyCode === $.ui.keyCode.ESCAPE ) { - that.close( event ); - event.preventDefault(); - } - }) - .mousedown(function( event ) { - that.moveToTop( false, event ); - }) - .appendTo( "body" ); - - this.element - .show() - .removeAttr( "title" ) - .addClass( "ui-dialog-content ui-widget-content" ) - .appendTo( uiDialog ); - - uiDialogTitlebar = ( this.uiDialogTitlebar = $( "
" ) ) - .addClass( "ui-dialog-titlebar ui-widget-header " + - "ui-corner-all ui-helper-clearfix" ) - .bind( "mousedown", function() { - // Dialog isn't getting focus when dragging (#8063) - uiDialog.focus(); - }) - .prependTo( uiDialog ); - - uiDialogTitlebarClose = $( "" ) - .addClass( "ui-dialog-titlebar-close ui-corner-all" ) - .attr( "role", "button" ) - .click(function( event ) { - event.preventDefault(); - that.close( event ); - }) - .appendTo( uiDialogTitlebar ); - - ( this.uiDialogTitlebarCloseText = $( "" ) ) - .addClass( "ui-icon ui-icon-closethick" ) - .text( options.closeText ) - .appendTo( uiDialogTitlebarClose ); - - uiDialogTitle = $( "" ) - .uniqueId() - .addClass( "ui-dialog-title" ) - .html( title ) - .prependTo( uiDialogTitlebar ); - - uiDialogButtonPane = ( this.uiDialogButtonPane = $( "
" ) ) - .addClass( "ui-dialog-buttonpane ui-widget-content ui-helper-clearfix" ); - - ( this.uiButtonSet = $( "
" ) ) - .addClass( "ui-dialog-buttonset" ) - .appendTo( uiDialogButtonPane ); - - uiDialog.attr({ - role: "dialog", - "aria-labelledby": uiDialogTitle.attr( "id" ) - }); - - uiDialogTitlebar.find( "*" ).add( uiDialogTitlebar ).disableSelection(); - this._hoverable( uiDialogTitlebarClose ); - this._focusable( uiDialogTitlebarClose ); - - if ( options.draggable && $.fn.draggable ) { - this._makeDraggable(); - } - if ( options.resizable && $.fn.resizable ) { - this._makeResizable(); - } - - this._createButtons( options.buttons ); - this._isOpen = false; - - if ( $.fn.bgiframe ) { - uiDialog.bgiframe(); - } - - // prevent tabbing out of modal dialogs - this._on( uiDialog, { keydown: function( event ) { - if ( !options.modal || event.keyCode !== $.ui.keyCode.TAB ) { - return; - } - - var tabbables = $( ":tabbable", uiDialog ), - first = tabbables.filter( ":first" ), - last = tabbables.filter( ":last" ); - - if ( event.target === last[0] && !event.shiftKey ) { - first.focus( 1 ); - return false; - } else if ( event.target === first[0] && event.shiftKey ) { - last.focus( 1 ); - return false; - } - }}); - }, - - _init: function() { - if ( this.options.autoOpen ) { - this.open(); - } - }, - - _destroy: function() { - var next, - oldPosition = this.oldPosition; - - if ( this.overlay ) { - this.overlay.destroy(); - } - this.uiDialog.hide(); - this.element - .removeClass( "ui-dialog-content ui-widget-content" ) - .hide() - .appendTo( "body" ); - this.uiDialog.remove(); - - if ( this.originalTitle ) { - this.element.attr( "title", this.originalTitle ); - } - - next = oldPosition.parent.children().eq( oldPosition.index ); - // Don't try to place the dialog next to itself (#8613) - if ( next.length && next[ 0 ] !== this.element[ 0 ] ) { - next.before( this.element ); - } else { - oldPosition.parent.append( this.element ); - } - }, - - widget: function() { - return this.uiDialog; - }, - - close: function( event ) { - var that = this, - maxZ, thisZ; - - if ( !this._isOpen ) { - return; - } - - if ( false === this._trigger( "beforeClose", event ) ) { - return; - } - - this._isOpen = false; - - if ( this.overlay ) { - this.overlay.destroy(); - } - - if ( this.options.hide ) { - this._hide( this.uiDialog, this.options.hide, function() { - that._trigger( "close", event ); - }); - } else { - this.uiDialog.hide(); - this._trigger( "close", event ); - } - - $.ui.dialog.overlay.resize(); - - // adjust the maxZ to allow other modal dialogs to continue to work (see #4309) - if ( this.options.modal ) { - maxZ = 0; - $( ".ui-dialog" ).each(function() { - if ( this !== that.uiDialog[0] ) { - thisZ = $( this ).css( "z-index" ); - if ( !isNaN( thisZ ) ) { - maxZ = Math.max( maxZ, thisZ ); - } - } - }); - $.ui.dialog.maxZ = maxZ; - } - - return this; - }, - - isOpen: function() { - return this._isOpen; - }, - - // the force parameter allows us to move modal dialogs to their correct - // position on open - moveToTop: function( force, event ) { - var options = this.options, - saveScroll; - - if ( ( options.modal && !force ) || - ( !options.stack && !options.modal ) ) { - return this._trigger( "focus", event ); - } - - if ( options.zIndex > $.ui.dialog.maxZ ) { - $.ui.dialog.maxZ = options.zIndex; - } - if ( this.overlay ) { - $.ui.dialog.maxZ += 1; - $.ui.dialog.overlay.maxZ = $.ui.dialog.maxZ; - this.overlay.$el.css( "z-index", $.ui.dialog.overlay.maxZ ); - } - - // Save and then restore scroll - // Opera 9.5+ resets when parent z-index is changed. - // http://bugs.jqueryui.com/ticket/3193 - saveScroll = { - scrollTop: this.element.scrollTop(), - scrollLeft: this.element.scrollLeft() - }; - $.ui.dialog.maxZ += 1; - this.uiDialog.css( "z-index", $.ui.dialog.maxZ ); - this.element.attr( saveScroll ); - this._trigger( "focus", event ); - - return this; - }, - - open: function() { - if ( this._isOpen ) { - return; - } - - var hasFocus, - options = this.options, - uiDialog = this.uiDialog; - - this._size(); - this._position( options.position ); - uiDialog.show( options.show ); - this.overlay = options.modal ? new $.ui.dialog.overlay( this ) : null; - this.moveToTop( true ); - - // set focus to the first tabbable element in the content area or the first button - // if there are no tabbable elements, set focus on the dialog itself - hasFocus = this.element.find( ":tabbable" ); - if ( !hasFocus.length ) { - hasFocus = this.uiDialogButtonPane.find( ":tabbable" ); - if ( !hasFocus.length ) { - hasFocus = uiDialog; - } - } - hasFocus.eq( 0 ).focus(); - - this._isOpen = true; - this._trigger( "open" ); - - return this; - }, - - _createButtons: function( buttons ) { - var that = this, - hasButtons = false; - - // if we already have a button pane, remove it - this.uiDialogButtonPane.remove(); - this.uiButtonSet.empty(); - - if ( typeof buttons === "object" && buttons !== null ) { - $.each( buttons, function() { - return !(hasButtons = true); - }); - } - if ( hasButtons ) { - $.each( buttons, function( name, props ) { - var button, click; - props = $.isFunction( props ) ? - { click: props, text: name } : - props; - // Default to a non-submitting button - props = $.extend( { type: "button" }, props ); - // Change the context for the click callback to be the main element - click = props.click; - props.click = function() { - click.apply( that.element[0], arguments ); - }; - button = $( "", props ) - .appendTo( that.uiButtonSet ); - if ( $.fn.button ) { - button.button(); - } - }); - this.uiDialog.addClass( "ui-dialog-buttons" ); - this.uiDialogButtonPane.appendTo( this.uiDialog ); - } else { - this.uiDialog.removeClass( "ui-dialog-buttons" ); - } - }, - - _makeDraggable: function() { - var that = this, - options = this.options; - - function filteredUi( ui ) { - return { - position: ui.position, - offset: ui.offset - }; - } - - this.uiDialog.draggable({ - cancel: ".ui-dialog-content, .ui-dialog-titlebar-close", - handle: ".ui-dialog-titlebar", - containment: "document", - start: function( event, ui ) { - $( this ) - .addClass( "ui-dialog-dragging" ); - that._trigger( "dragStart", event, filteredUi( ui ) ); - }, - drag: function( event, ui ) { - that._trigger( "drag", event, filteredUi( ui ) ); - }, - stop: function( event, ui ) { - options.position = [ - ui.position.left - that.document.scrollLeft(), - ui.position.top - that.document.scrollTop() - ]; - $( this ) - .removeClass( "ui-dialog-dragging" ); - that._trigger( "dragStop", event, filteredUi( ui ) ); - $.ui.dialog.overlay.resize(); - } - }); - }, - - _makeResizable: function( handles ) { - handles = (handles === undefined ? this.options.resizable : handles); - var that = this, - options = this.options, - // .ui-resizable has position: relative defined in the stylesheet - // but dialogs have to use absolute or fixed positioning - position = this.uiDialog.css( "position" ), - resizeHandles = typeof handles === 'string' ? - handles : - "n,e,s,w,se,sw,ne,nw"; - - function filteredUi( ui ) { - return { - originalPosition: ui.originalPosition, - originalSize: ui.originalSize, - position: ui.position, - size: ui.size - }; - } - - this.uiDialog.resizable({ - cancel: ".ui-dialog-content", - containment: "document", - alsoResize: this.element, - maxWidth: options.maxWidth, - maxHeight: options.maxHeight, - minWidth: options.minWidth, - minHeight: this._minHeight(), - handles: resizeHandles, - start: function( event, ui ) { - $( this ).addClass( "ui-dialog-resizing" ); - that._trigger( "resizeStart", event, filteredUi( ui ) ); - }, - resize: function( event, ui ) { - that._trigger( "resize", event, filteredUi( ui ) ); - }, - stop: function( event, ui ) { - $( this ).removeClass( "ui-dialog-resizing" ); - options.height = $( this ).height(); - options.width = $( this ).width(); - that._trigger( "resizeStop", event, filteredUi( ui ) ); - $.ui.dialog.overlay.resize(); - } - }) - .css( "position", position ) - .find( ".ui-resizable-se" ) - .addClass( "ui-icon ui-icon-grip-diagonal-se" ); - }, - - _minHeight: function() { - var options = this.options; - - if ( options.height === "auto" ) { - return options.minHeight; - } else { - return Math.min( options.minHeight, options.height ); - } - }, - - _position: function( position ) { - var myAt = [], - offset = [ 0, 0 ], - isVisible; - - if ( position ) { - // deep extending converts arrays to objects in jQuery <= 1.3.2 :-( - // if (typeof position == 'string' || $.isArray(position)) { - // myAt = $.isArray(position) ? position : position.split(' '); - - if ( typeof position === "string" || (typeof position === "object" && "0" in position ) ) { - myAt = position.split ? position.split( " " ) : [ position[ 0 ], position[ 1 ] ]; - if ( myAt.length === 1 ) { - myAt[ 1 ] = myAt[ 0 ]; - } - - $.each( [ "left", "top" ], function( i, offsetPosition ) { - if ( +myAt[ i ] === myAt[ i ] ) { - offset[ i ] = myAt[ i ]; - myAt[ i ] = offsetPosition; - } - }); - - position = { - my: myAt[0] + (offset[0] < 0 ? offset[0] : "+" + offset[0]) + " " + - myAt[1] + (offset[1] < 0 ? offset[1] : "+" + offset[1]), - at: myAt.join( " " ) - }; - } - - position = $.extend( {}, $.ui.dialog.prototype.options.position, position ); - } else { - position = $.ui.dialog.prototype.options.position; - } - - // need to show the dialog to get the actual offset in the position plugin - isVisible = this.uiDialog.is( ":visible" ); - if ( !isVisible ) { - this.uiDialog.show(); - } - this.uiDialog.position( position ); - if ( !isVisible ) { - this.uiDialog.hide(); - } - }, - - _setOptions: function( options ) { - var that = this, - resizableOptions = {}, - resize = false; - - $.each( options, function( key, value ) { - that._setOption( key, value ); - - if ( key in sizeRelatedOptions ) { - resize = true; - } - if ( key in resizableRelatedOptions ) { - resizableOptions[ key ] = value; - } - }); - - if ( resize ) { - this._size(); - } - if ( this.uiDialog.is( ":data(resizable)" ) ) { - this.uiDialog.resizable( "option", resizableOptions ); - } - }, - - _setOption: function( key, value ) { - var isDraggable, isResizable, - uiDialog = this.uiDialog; - - switch ( key ) { - case "buttons": - this._createButtons( value ); - break; - case "closeText": - // ensure that we always pass a string - this.uiDialogTitlebarCloseText.text( "" + value ); - break; - case "dialogClass": - uiDialog - .removeClass( this.options.dialogClass ) - .addClass( uiDialogClasses + value ); - break; - case "disabled": - if ( value ) { - uiDialog.addClass( "ui-dialog-disabled" ); - } else { - uiDialog.removeClass( "ui-dialog-disabled" ); - } - break; - case "draggable": - isDraggable = uiDialog.is( ":data(draggable)" ); - if ( isDraggable && !value ) { - uiDialog.draggable( "destroy" ); - } - - if ( !isDraggable && value ) { - this._makeDraggable(); - } - break; - case "position": - this._position( value ); - break; - case "resizable": - // currently resizable, becoming non-resizable - isResizable = uiDialog.is( ":data(resizable)" ); - if ( isResizable && !value ) { - uiDialog.resizable( "destroy" ); - } - - // currently resizable, changing handles - if ( isResizable && typeof value === "string" ) { - uiDialog.resizable( "option", "handles", value ); - } - - // currently non-resizable, becoming resizable - if ( !isResizable && value !== false ) { - this._makeResizable( value ); - } - break; - case "title": - // convert whatever was passed in o a string, for html() to not throw up - $( ".ui-dialog-title", this.uiDialogTitlebar ) - .html( "" + ( value || " " ) ); - break; - } - - this._super( key, value ); - }, - - _size: function() { - /* If the user has resized the dialog, the .ui-dialog and .ui-dialog-content - * divs will both have width and height set, so we need to reset them - */ - var nonContentHeight, minContentHeight, autoHeight, - options = this.options, - isVisible = this.uiDialog.is( ":visible" ); - - // reset content sizing - this.element.show().css({ - width: "auto", - minHeight: 0, - height: 0 - }); - - if ( options.minWidth > options.width ) { - options.width = options.minWidth; - } - - // reset wrapper sizing - // determine the height of all the non-content elements - nonContentHeight = this.uiDialog.css({ - height: "auto", - width: options.width - }) - .outerHeight(); - minContentHeight = Math.max( 0, options.minHeight - nonContentHeight ); - - if ( options.height === "auto" ) { - // only needed for IE6 support - if ( $.support.minHeight ) { - this.element.css({ - minHeight: minContentHeight, - height: "auto" - }); - } else { - this.uiDialog.show(); - autoHeight = this.element.css( "height", "auto" ).height(); - if ( !isVisible ) { - this.uiDialog.hide(); - } - this.element.height( Math.max( autoHeight, minContentHeight ) ); - } - } else { - this.element.height( Math.max( options.height - nonContentHeight, 0 ) ); - } - - if (this.uiDialog.is( ":data(resizable)" ) ) { - this.uiDialog.resizable( "option", "minHeight", this._minHeight() ); - } - } -}); - -$.extend($.ui.dialog, { - uuid: 0, - maxZ: 0, - - getTitleId: function($el) { - var id = $el.attr( "id" ); - if ( !id ) { - this.uuid += 1; - id = this.uuid; - } - return "ui-dialog-title-" + id; - }, - - overlay: function( dialog ) { - this.$el = $.ui.dialog.overlay.create( dialog ); - } -}); - -$.extend( $.ui.dialog.overlay, { - instances: [], - // reuse old instances due to IE memory leak with alpha transparency (see #5185) - oldInstances: [], - maxZ: 0, - events: $.map( - "focus,mousedown,mouseup,keydown,keypress,click".split( "," ), - function( event ) { - return event + ".dialog-overlay"; - } - ).join( " " ), - create: function( dialog ) { - if ( this.instances.length === 0 ) { - // prevent use of anchors and inputs - // we use a setTimeout in case the overlay is created from an - // event that we're going to be cancelling (see #2804) - setTimeout(function() { - // handle $(el).dialog().dialog('close') (see #4065) - if ( $.ui.dialog.overlay.instances.length ) { - $( document ).bind( $.ui.dialog.overlay.events, function( event ) { - // stop events if the z-index of the target is < the z-index of the overlay - // we cannot return true when we don't want to cancel the event (#3523) - if ( $( event.target ).zIndex() < $.ui.dialog.overlay.maxZ ) { - return false; - } - }); - } - }, 1 ); - - // handle window resize - $( window ).bind( "resize.dialog-overlay", $.ui.dialog.overlay.resize ); - } - - var $el = ( this.oldInstances.pop() || $( "
" ).addClass( "ui-widget-overlay" ) ); - - // allow closing by pressing the escape key - $( document ).bind( "keydown.dialog-overlay", function( event ) { - var instances = $.ui.dialog.overlay.instances; - // only react to the event if we're the top overlay - if ( instances.length !== 0 && instances[ instances.length - 1 ] === $el && - dialog.options.closeOnEscape && !event.isDefaultPrevented() && event.keyCode && - event.keyCode === $.ui.keyCode.ESCAPE ) { - - dialog.close( event ); - event.preventDefault(); - } - }); - - $el.appendTo( document.body ).css({ - width: this.width(), - height: this.height() - }); - - if ( $.fn.bgiframe ) { - $el.bgiframe(); - } - - this.instances.push( $el ); - return $el; - }, - - destroy: function( $el ) { - var indexOf = $.inArray( $el, this.instances ), - maxZ = 0; - - if ( indexOf !== -1 ) { - this.oldInstances.push( this.instances.splice( indexOf, 1 )[ 0 ] ); - } - - if ( this.instances.length === 0 ) { - $( [ document, window ] ).unbind( ".dialog-overlay" ); - } - - $el.height( 0 ).width( 0 ).remove(); - - // adjust the maxZ to allow other modal dialogs to continue to work (see #4309) - $.each( this.instances, function() { - maxZ = Math.max( maxZ, this.css( "z-index" ) ); - }); - this.maxZ = maxZ; - }, - - height: function() { - var scrollHeight, - offsetHeight; - // handle IE - if ( $.ui.ie ) { - scrollHeight = Math.max( - document.documentElement.scrollHeight, - document.body.scrollHeight - ); - offsetHeight = Math.max( - document.documentElement.offsetHeight, - document.body.offsetHeight - ); - - if ( scrollHeight < offsetHeight ) { - return $( window ).height() + "px"; - } else { - return scrollHeight + "px"; - } - // handle "good" browsers - } else { - return $( document ).height() + "px"; - } - }, - - width: function() { - var scrollWidth, - offsetWidth; - // handle IE - if ( $.ui.ie ) { - scrollWidth = Math.max( - document.documentElement.scrollWidth, - document.body.scrollWidth - ); - offsetWidth = Math.max( - document.documentElement.offsetWidth, - document.body.offsetWidth - ); - - if ( scrollWidth < offsetWidth ) { - return $( window ).width() + "px"; - } else { - return scrollWidth + "px"; - } - // handle "good" browsers - } else { - return $( document ).width() + "px"; - } - }, - - resize: function() { - /* If the dialog is draggable and the user drags it past the - * right edge of the window, the document becomes wider so we - * need to stretch the overlay. If the user then drags the - * dialog back to the left, the document will become narrower, - * so we need to shrink the overlay to the appropriate size. - * This is handled by shrinking the overlay before setting it - * to the full document size. - */ - var $overlays = $( [] ); - $.each( $.ui.dialog.overlay.instances, function() { - $overlays = $overlays.add( this ); - }); - - $overlays.css({ - width: 0, - height: 0 - }).css({ - width: $.ui.dialog.overlay.width(), - height: $.ui.dialog.overlay.height() - }); - } -}); - -$.extend( $.ui.dialog.overlay.prototype, { - destroy: function() { - $.ui.dialog.overlay.destroy( this.$el ); - } -}); - -}( jQuery ) ); - -(function( $, undefined ) { - -var rvertical = /up|down|vertical/, - rpositivemotion = /up|left|vertical|horizontal/; - -$.effects.effect.blind = function( o, done ) { - // Create element - var el = $( this ), - props = [ "position", "top", "bottom", "left", "right", "height", "width" ], - mode = $.effects.setMode( el, o.mode || "hide" ), - direction = o.direction || "up", - vertical = rvertical.test( direction ), - ref = vertical ? "height" : "width", - ref2 = vertical ? "top" : "left", - motion = rpositivemotion.test( direction ), - animation = {}, - show = mode === "show", - wrapper, distance, margin; - - // if already wrapped, the wrapper's properties are my property. #6245 - if ( el.parent().is( ".ui-effects-wrapper" ) ) { - $.effects.save( el.parent(), props ); - } else { - $.effects.save( el, props ); - } - el.show(); - wrapper = $.effects.createWrapper( el ).css({ - overflow: "hidden" - }); - - distance = wrapper[ ref ](); - margin = parseFloat( wrapper.css( ref2 ) ) || 0; - - animation[ ref ] = show ? distance : 0; - if ( !motion ) { - el - .css( vertical ? "bottom" : "right", 0 ) - .css( vertical ? "top" : "left", "auto" ) - .css({ position: "absolute" }); - - animation[ ref2 ] = show ? margin : distance + margin; - } - - // start at 0 if we are showing - if ( show ) { - wrapper.css( ref, 0 ); - if ( ! motion ) { - wrapper.css( ref2, margin + distance ); - } - } - - // Animate - wrapper.animate( animation, { - duration: o.duration, - easing: o.easing, - queue: false, - complete: function() { - if ( mode === "hide" ) { - el.hide(); - } - $.effects.restore( el, props ); - $.effects.removeWrapper( el ); - done(); - } - }); - -}; - -})(jQuery); - -(function( $, undefined ) { - -$.effects.effect.bounce = function( o, done ) { - var el = $( this ), - props = [ "position", "top", "bottom", "left", "right", "height", "width" ], - - // defaults: - mode = $.effects.setMode( el, o.mode || "effect" ), - hide = mode === "hide", - show = mode === "show", - direction = o.direction || "up", - distance = o.distance, - times = o.times || 5, - - // number of internal animations - anims = times * 2 + ( show || hide ? 1 : 0 ), - speed = o.duration / anims, - easing = o.easing, - - // utility: - ref = ( direction === "up" || direction === "down" ) ? "top" : "left", - motion = ( direction === "up" || direction === "left" ), - i, - upAnim, - downAnim, - - // we will need to re-assemble the queue to stack our animations in place - queue = el.queue(), - queuelen = queue.length; - - // Avoid touching opacity to prevent clearType and PNG issues in IE - if ( show || hide ) { - props.push( "opacity" ); - } - - $.effects.save( el, props ); - el.show(); - $.effects.createWrapper( el ); // Create Wrapper - - // default distance for the BIGGEST bounce is the outer Distance / 3 - if ( !distance ) { - distance = el[ ref === "top" ? "outerHeight" : "outerWidth" ]() / 3; - } - - if ( show ) { - downAnim = { opacity: 1 }; - downAnim[ ref ] = 0; - - // if we are showing, force opacity 0 and set the initial position - // then do the "first" animation - el.css( "opacity", 0 ) - .css( ref, motion ? -distance * 2 : distance * 2 ) - .animate( downAnim, speed, easing ); - } - - // start at the smallest distance if we are hiding - if ( hide ) { - distance = distance / Math.pow( 2, times - 1 ); - } - - downAnim = {}; - downAnim[ ref ] = 0; - // Bounces up/down/left/right then back to 0 -- times * 2 animations happen here - for ( i = 0; i < times; i++ ) { - upAnim = {}; - upAnim[ ref ] = ( motion ? "-=" : "+=" ) + distance; - - el.animate( upAnim, speed, easing ) - .animate( downAnim, speed, easing ); - - distance = hide ? distance * 2 : distance / 2; - } - - // Last Bounce when Hiding - if ( hide ) { - upAnim = { opacity: 0 }; - upAnim[ ref ] = ( motion ? "-=" : "+=" ) + distance; - - el.animate( upAnim, speed, easing ); - } - - el.queue(function() { - if ( hide ) { - el.hide(); - } - $.effects.restore( el, props ); - $.effects.removeWrapper( el ); - done(); - }); - - // inject all the animations we just queued to be first in line (after "inprogress") - if ( queuelen > 1) { - queue.splice.apply( queue, - [ 1, 0 ].concat( queue.splice( queuelen, anims + 1 ) ) ); - } - el.dequeue(); - -}; - -})(jQuery); - -(function( $, undefined ) { - -$.effects.effect.clip = function( o, done ) { - // Create element - var el = $( this ), - props = [ "position", "top", "bottom", "left", "right", "height", "width" ], - mode = $.effects.setMode( el, o.mode || "hide" ), - show = mode === "show", - direction = o.direction || "vertical", - vert = direction === "vertical", - size = vert ? "height" : "width", - position = vert ? "top" : "left", - animation = {}, - wrapper, animate, distance; - - // Save & Show - $.effects.save( el, props ); - el.show(); - - // Create Wrapper - wrapper = $.effects.createWrapper( el ).css({ - overflow: "hidden" - }); - animate = ( el[0].tagName === "IMG" ) ? wrapper : el; - distance = animate[ size ](); - - // Shift - if ( show ) { - animate.css( size, 0 ); - animate.css( position, distance / 2 ); - } - - // Create Animation Object: - animation[ size ] = show ? distance : 0; - animation[ position ] = show ? 0 : distance / 2; - - // Animate - animate.animate( animation, { - queue: false, - duration: o.duration, - easing: o.easing, - complete: function() { - if ( !show ) { - el.hide(); - } - $.effects.restore( el, props ); - $.effects.removeWrapper( el ); - done(); - } - }); - -}; - -})(jQuery); - -(function( $, undefined ) { - -$.effects.effect.drop = function( o, done ) { - - var el = $( this ), - props = [ "position", "top", "bottom", "left", "right", "opacity", "height", "width" ], - mode = $.effects.setMode( el, o.mode || "hide" ), - show = mode === "show", - direction = o.direction || "left", - ref = ( direction === "up" || direction === "down" ) ? "top" : "left", - motion = ( direction === "up" || direction === "left" ) ? "pos" : "neg", - animation = { - opacity: show ? 1 : 0 - }, - distance; - - // Adjust - $.effects.save( el, props ); - el.show(); - $.effects.createWrapper( el ); - - distance = o.distance || el[ ref === "top" ? "outerHeight": "outerWidth" ]( true ) / 2; - - if ( show ) { - el - .css( "opacity", 0 ) - .css( ref, motion === "pos" ? -distance : distance ); - } - - // Animation - animation[ ref ] = ( show ? - ( motion === "pos" ? "+=" : "-=" ) : - ( motion === "pos" ? "-=" : "+=" ) ) + - distance; - - // Animate - el.animate( animation, { - queue: false, - duration: o.duration, - easing: o.easing, - complete: function() { - if ( mode === "hide" ) { - el.hide(); - } - $.effects.restore( el, props ); - $.effects.removeWrapper( el ); - done(); - } - }); -}; - -})(jQuery); - -(function( $, undefined ) { - -$.effects.effect.explode = function( o, done ) { - - var rows = o.pieces ? Math.round( Math.sqrt( o.pieces ) ) : 3, - cells = rows, - el = $( this ), - mode = $.effects.setMode( el, o.mode || "hide" ), - show = mode === "show", - - // show and then visibility:hidden the element before calculating offset - offset = el.show().css( "visibility", "hidden" ).offset(), - - // width and height of a piece - width = Math.ceil( el.outerWidth() / cells ), - height = Math.ceil( el.outerHeight() / rows ), - pieces = [], - - // loop - i, j, left, top, mx, my; - - // children animate complete: - function childComplete() { - pieces.push( this ); - if ( pieces.length === rows * cells ) { - animComplete(); - } - } - - // clone the element for each row and cell. - for( i = 0; i < rows ; i++ ) { // ===> - top = offset.top + i * height; - my = i - ( rows - 1 ) / 2 ; - - for( j = 0; j < cells ; j++ ) { // ||| - left = offset.left + j * width; - mx = j - ( cells - 1 ) / 2 ; - - // Create a clone of the now hidden main element that will be absolute positioned - // within a wrapper div off the -left and -top equal to size of our pieces - el - .clone() - .appendTo( "body" ) - .wrap( "
" ) - .css({ - position: "absolute", - visibility: "visible", - left: -j * width, - top: -i * height - }) - - // select the wrapper - make it overflow: hidden and absolute positioned based on - // where the original was located +left and +top equal to the size of pieces - .parent() - .addClass( "ui-effects-explode" ) - .css({ - position: "absolute", - overflow: "hidden", - width: width, - height: height, - left: left + ( show ? mx * width : 0 ), - top: top + ( show ? my * height : 0 ), - opacity: show ? 0 : 1 - }).animate({ - left: left + ( show ? 0 : mx * width ), - top: top + ( show ? 0 : my * height ), - opacity: show ? 1 : 0 - }, o.duration || 500, o.easing, childComplete ); - } - } - - function animComplete() { - el.css({ - visibility: "visible" - }); - $( pieces ).remove(); - if ( !show ) { - el.hide(); - } - done(); - } -}; - -})(jQuery); - -(function( $, undefined ) { - -$.effects.effect.fade = function( o, done ) { - var el = $( this ), - mode = $.effects.setMode( el, o.mode || "toggle" ); - - el.animate({ - opacity: mode - }, { - queue: false, - duration: o.duration, - easing: o.easing, - complete: done - }); -}; - -})( jQuery ); - -(function( $, undefined ) { - -$.effects.effect.fold = function( o, done ) { - - // Create element - var el = $( this ), - props = [ "position", "top", "bottom", "left", "right", "height", "width" ], - mode = $.effects.setMode( el, o.mode || "hide" ), - show = mode === "show", - hide = mode === "hide", - size = o.size || 15, - percent = /([0-9]+)%/.exec( size ), - horizFirst = !!o.horizFirst, - widthFirst = show !== horizFirst, - ref = widthFirst ? [ "width", "height" ] : [ "height", "width" ], - duration = o.duration / 2, - wrapper, distance, - animation1 = {}, - animation2 = {}; - - $.effects.save( el, props ); - el.show(); - - // Create Wrapper - wrapper = $.effects.createWrapper( el ).css({ - overflow: "hidden" - }); - distance = widthFirst ? - [ wrapper.width(), wrapper.height() ] : - [ wrapper.height(), wrapper.width() ]; - - if ( percent ) { - size = parseInt( percent[ 1 ], 10 ) / 100 * distance[ hide ? 0 : 1 ]; - } - if ( show ) { - wrapper.css( horizFirst ? { - height: 0, - width: size - } : { - height: size, - width: 0 - }); - } - - // Animation - animation1[ ref[ 0 ] ] = show ? distance[ 0 ] : size; - animation2[ ref[ 1 ] ] = show ? distance[ 1 ] : 0; - - // Animate - wrapper - .animate( animation1, duration, o.easing ) - .animate( animation2, duration, o.easing, function() { - if ( hide ) { - el.hide(); - } - $.effects.restore( el, props ); - $.effects.removeWrapper( el ); - done(); - }); - -}; - -})(jQuery); - -(function( $, undefined ) { - -$.effects.effect.highlight = function( o, done ) { - var elem = $( this ), - props = [ "backgroundImage", "backgroundColor", "opacity" ], - mode = $.effects.setMode( elem, o.mode || "show" ), - animation = { - backgroundColor: elem.css( "backgroundColor" ) - }; - - if (mode === "hide") { - animation.opacity = 0; - } - - $.effects.save( elem, props ); - - elem - .show() - .css({ - backgroundImage: "none", - backgroundColor: o.color || "#ffff99" - }) - .animate( animation, { - queue: false, - duration: o.duration, - easing: o.easing, - complete: function() { - if ( mode === "hide" ) { - elem.hide(); - } - $.effects.restore( elem, props ); - done(); - } - }); -}; - -})(jQuery); - -(function( $, undefined ) { - -$.effects.effect.pulsate = function( o, done ) { - var elem = $( this ), - mode = $.effects.setMode( elem, o.mode || "show" ), - show = mode === "show", - hide = mode === "hide", - showhide = ( show || mode === "hide" ), - - // showing or hiding leaves of the "last" animation - anims = ( ( o.times || 5 ) * 2 ) + ( showhide ? 1 : 0 ), - duration = o.duration / anims, - animateTo = 0, - queue = elem.queue(), - queuelen = queue.length, - i; - - if ( show || !elem.is(":visible")) { - elem.css( "opacity", 0 ).show(); - animateTo = 1; - } - - // anims - 1 opacity "toggles" - for ( i = 1; i < anims; i++ ) { - elem.animate({ - opacity: animateTo - }, duration, o.easing ); - animateTo = 1 - animateTo; - } - - elem.animate({ - opacity: animateTo - }, duration, o.easing); - - elem.queue(function() { - if ( hide ) { - elem.hide(); - } - done(); - }); - - // We just queued up "anims" animations, we need to put them next in the queue - if ( queuelen > 1 ) { - queue.splice.apply( queue, - [ 1, 0 ].concat( queue.splice( queuelen, anims + 1 ) ) ); - } - elem.dequeue(); -}; - -})(jQuery); - -(function( $, undefined ) { - -$.effects.effect.puff = function( o, done ) { - var elem = $( this ), - mode = $.effects.setMode( elem, o.mode || "hide" ), - hide = mode === "hide", - percent = parseInt( o.percent, 10 ) || 150, - factor = percent / 100, - original = { - height: elem.height(), - width: elem.width(), - outerHeight: elem.outerHeight(), - outerWidth: elem.outerWidth() - }; - - $.extend( o, { - effect: "scale", - queue: false, - fade: true, - mode: mode, - complete: done, - percent: hide ? percent : 100, - from: hide ? - original : - { - height: original.height * factor, - width: original.width * factor, - outerHeight: original.outerHeight * factor, - outerWidth: original.outerWidth * factor - } - }); - - elem.effect( o ); -}; - -$.effects.effect.scale = function( o, done ) { - - // Create element - var el = $( this ), - options = $.extend( true, {}, o ), - mode = $.effects.setMode( el, o.mode || "effect" ), - percent = parseInt( o.percent, 10 ) || - ( parseInt( o.percent, 10 ) === 0 ? 0 : ( mode === "hide" ? 0 : 100 ) ), - direction = o.direction || "both", - origin = o.origin, - original = { - height: el.height(), - width: el.width(), - outerHeight: el.outerHeight(), - outerWidth: el.outerWidth() - }, - factor = { - y: direction !== "horizontal" ? (percent / 100) : 1, - x: direction !== "vertical" ? (percent / 100) : 1 - }; - - // We are going to pass this effect to the size effect: - options.effect = "size"; - options.queue = false; - options.complete = done; - - // Set default origin and restore for show/hide - if ( mode !== "effect" ) { - options.origin = origin || ["middle","center"]; - options.restore = true; - } - - options.from = o.from || ( mode === "show" ? { - height: 0, - width: 0, - outerHeight: 0, - outerWidth: 0 - } : original ); - options.to = { - height: original.height * factor.y, - width: original.width * factor.x, - outerHeight: original.outerHeight * factor.y, - outerWidth: original.outerWidth * factor.x - }; - - // Fade option to support puff - if ( options.fade ) { - if ( mode === "show" ) { - options.from.opacity = 0; - options.to.opacity = 1; - } - if ( mode === "hide" ) { - options.from.opacity = 1; - options.to.opacity = 0; - } - } - - // Animate - el.effect( options ); - -}; - -$.effects.effect.size = function( o, done ) { - - // Create element - var original, baseline, factor, - el = $( this ), - props0 = [ "position", "top", "bottom", "left", "right", "width", "height", "overflow", "opacity" ], - - // Always restore - props1 = [ "position", "top", "bottom", "left", "right", "overflow", "opacity" ], - - // Copy for children - props2 = [ "width", "height", "overflow" ], - cProps = [ "fontSize" ], - vProps = [ "borderTopWidth", "borderBottomWidth", "paddingTop", "paddingBottom" ], - hProps = [ "borderLeftWidth", "borderRightWidth", "paddingLeft", "paddingRight" ], - - // Set options - mode = $.effects.setMode( el, o.mode || "effect" ), - restore = o.restore || mode !== "effect", - scale = o.scale || "both", - origin = o.origin || [ "middle", "center" ], - position = el.css( "position" ), - props = restore ? props0 : props1, - zero = { - height: 0, - width: 0, - outerHeight: 0, - outerWidth: 0 - }; - - if ( mode === "show" ) { - el.show(); - } - original = { - height: el.height(), - width: el.width(), - outerHeight: el.outerHeight(), - outerWidth: el.outerWidth() - }; - - if ( o.mode === "toggle" && mode === "show" ) { - el.from = o.to || zero; - el.to = o.from || original; - } else { - el.from = o.from || ( mode === "show" ? zero : original ); - el.to = o.to || ( mode === "hide" ? zero : original ); - } - - // Set scaling factor - factor = { - from: { - y: el.from.height / original.height, - x: el.from.width / original.width - }, - to: { - y: el.to.height / original.height, - x: el.to.width / original.width - } - }; - - // Scale the css box - if ( scale === "box" || scale === "both" ) { - - // Vertical props scaling - if ( factor.from.y !== factor.to.y ) { - props = props.concat( vProps ); - el.from = $.effects.setTransition( el, vProps, factor.from.y, el.from ); - el.to = $.effects.setTransition( el, vProps, factor.to.y, el.to ); - } - - // Horizontal props scaling - if ( factor.from.x !== factor.to.x ) { - props = props.concat( hProps ); - el.from = $.effects.setTransition( el, hProps, factor.from.x, el.from ); - el.to = $.effects.setTransition( el, hProps, factor.to.x, el.to ); - } - } - - // Scale the content - if ( scale === "content" || scale === "both" ) { - - // Vertical props scaling - if ( factor.from.y !== factor.to.y ) { - props = props.concat( cProps ).concat( props2 ); - el.from = $.effects.setTransition( el, cProps, factor.from.y, el.from ); - el.to = $.effects.setTransition( el, cProps, factor.to.y, el.to ); - } - } - - $.effects.save( el, props ); - el.show(); - $.effects.createWrapper( el ); - el.css( "overflow", "hidden" ).css( el.from ); - - // Adjust - if (origin) { // Calculate baseline shifts - baseline = $.effects.getBaseline( origin, original ); - el.from.top = ( original.outerHeight - el.outerHeight() ) * baseline.y; - el.from.left = ( original.outerWidth - el.outerWidth() ) * baseline.x; - el.to.top = ( original.outerHeight - el.to.outerHeight ) * baseline.y; - el.to.left = ( original.outerWidth - el.to.outerWidth ) * baseline.x; - } - el.css( el.from ); // set top & left - - // Animate - if ( scale === "content" || scale === "both" ) { // Scale the children - - // Add margins/font-size - vProps = vProps.concat([ "marginTop", "marginBottom" ]).concat(cProps); - hProps = hProps.concat([ "marginLeft", "marginRight" ]); - props2 = props0.concat(vProps).concat(hProps); - - el.find( "*[width]" ).each( function(){ - var child = $( this ), - c_original = { - height: child.height(), - width: child.width(), - outerHeight: child.outerHeight(), - outerWidth: child.outerWidth() - }; - if (restore) { - $.effects.save(child, props2); - } - - child.from = { - height: c_original.height * factor.from.y, - width: c_original.width * factor.from.x, - outerHeight: c_original.outerHeight * factor.from.y, - outerWidth: c_original.outerWidth * factor.from.x - }; - child.to = { - height: c_original.height * factor.to.y, - width: c_original.width * factor.to.x, - outerHeight: c_original.height * factor.to.y, - outerWidth: c_original.width * factor.to.x - }; - - // Vertical props scaling - if ( factor.from.y !== factor.to.y ) { - child.from = $.effects.setTransition( child, vProps, factor.from.y, child.from ); - child.to = $.effects.setTransition( child, vProps, factor.to.y, child.to ); - } - - // Horizontal props scaling - if ( factor.from.x !== factor.to.x ) { - child.from = $.effects.setTransition( child, hProps, factor.from.x, child.from ); - child.to = $.effects.setTransition( child, hProps, factor.to.x, child.to ); - } - - // Animate children - child.css( child.from ); - child.animate( child.to, o.duration, o.easing, function() { - - // Restore children - if ( restore ) { - $.effects.restore( child, props2 ); - } - }); - }); - } - - // Animate - el.animate( el.to, { - queue: false, - duration: o.duration, - easing: o.easing, - complete: function() { - if ( el.to.opacity === 0 ) { - el.css( "opacity", el.from.opacity ); - } - if( mode === "hide" ) { - el.hide(); - } - $.effects.restore( el, props ); - if ( !restore ) { - - // we need to calculate our new positioning based on the scaling - if ( position === "static" ) { - el.css({ - position: "relative", - top: el.to.top, - left: el.to.left - }); - } else { - $.each([ "top", "left" ], function( idx, pos ) { - el.css( pos, function( _, str ) { - var val = parseInt( str, 10 ), - toRef = idx ? el.to.left : el.to.top; - - // if original was "auto", recalculate the new value from wrapper - if ( str === "auto" ) { - return toRef + "px"; - } - - return val + toRef + "px"; - }); - }); - } - } - - $.effects.removeWrapper( el ); - done(); - } - }); - -}; - -})(jQuery); - -(function( $, undefined ) { - -$.effects.effect.shake = function( o, done ) { - - var el = $( this ), - props = [ "position", "top", "bottom", "left", "right", "height", "width" ], - mode = $.effects.setMode( el, o.mode || "effect" ), - direction = o.direction || "left", - distance = o.distance || 20, - times = o.times || 3, - anims = times * 2 + 1, - speed = Math.round(o.duration/anims), - ref = (direction === "up" || direction === "down") ? "top" : "left", - positiveMotion = (direction === "up" || direction === "left"), - animation = {}, - animation1 = {}, - animation2 = {}, - i, - - // we will need to re-assemble the queue to stack our animations in place - queue = el.queue(), - queuelen = queue.length; - - $.effects.save( el, props ); - el.show(); - $.effects.createWrapper( el ); - - // Animation - animation[ ref ] = ( positiveMotion ? "-=" : "+=" ) + distance; - animation1[ ref ] = ( positiveMotion ? "+=" : "-=" ) + distance * 2; - animation2[ ref ] = ( positiveMotion ? "-=" : "+=" ) + distance * 2; - - // Animate - el.animate( animation, speed, o.easing ); - - // Shakes - for ( i = 1; i < times; i++ ) { - el.animate( animation1, speed, o.easing ).animate( animation2, speed, o.easing ); - } - el - .animate( animation1, speed, o.easing ) - .animate( animation, speed / 2, o.easing ) - .queue(function() { - if ( mode === "hide" ) { - el.hide(); - } - $.effects.restore( el, props ); - $.effects.removeWrapper( el ); - done(); - }); - - // inject all the animations we just queued to be first in line (after "inprogress") - if ( queuelen > 1) { - queue.splice.apply( queue, - [ 1, 0 ].concat( queue.splice( queuelen, anims + 1 ) ) ); - } - el.dequeue(); - -}; - -})(jQuery); - -(function( $, undefined ) { - -$.effects.effect.slide = function( o, done ) { - - // Create element - var el = $( this ), - props = [ "position", "top", "bottom", "left", "right", "width", "height" ], - mode = $.effects.setMode( el, o.mode || "show" ), - show = mode === "show", - direction = o.direction || "left", - ref = (direction === "up" || direction === "down") ? "top" : "left", - positiveMotion = (direction === "up" || direction === "left"), - distance, - animation = {}; - - // Adjust - $.effects.save( el, props ); - el.show(); - distance = o.distance || el[ ref === "top" ? "outerHeight" : "outerWidth" ]( true ); - - $.effects.createWrapper( el ).css({ - overflow: "hidden" - }); - - if ( show ) { - el.css( ref, positiveMotion ? (isNaN(distance) ? "-" + distance : -distance) : distance ); - } - - // Animation - animation[ ref ] = ( show ? - ( positiveMotion ? "+=" : "-=") : - ( positiveMotion ? "-=" : "+=")) + - distance; - - // Animate - el.animate( animation, { - queue: false, - duration: o.duration, - easing: o.easing, - complete: function() { - if ( mode === "hide" ) { - el.hide(); - } - $.effects.restore( el, props ); - $.effects.removeWrapper( el ); - done(); - } - }); -}; - -})(jQuery); - -(function( $, undefined ) { - -$.effects.effect.transfer = function( o, done ) { - var elem = $( this ), - target = $( o.to ), - targetFixed = target.css( "position" ) === "fixed", - body = $("body"), - fixTop = targetFixed ? body.scrollTop() : 0, - fixLeft = targetFixed ? body.scrollLeft() : 0, - endPosition = target.offset(), - animation = { - top: endPosition.top - fixTop , - left: endPosition.left - fixLeft , - height: target.innerHeight(), - width: target.innerWidth() - }, - startPosition = elem.offset(), - transfer = $( '
' ) - .appendTo( document.body ) - .addClass( o.className ) - .css({ - top: startPosition.top - fixTop , - left: startPosition.left - fixLeft , - height: elem.innerHeight(), - width: elem.innerWidth(), - position: targetFixed ? "fixed" : "absolute" - }) - .animate( animation, o.duration, o.easing, function() { - transfer.remove(); - done(); - }); -}; - -})(jQuery); - -(function( $, undefined ) { - -var mouseHandled = false; - -$.widget( "ui.menu", { - version: "1.9.2", - defaultElement: "
    ", - delay: 300, - options: { - icons: { - submenu: "ui-icon-carat-1-e" - }, - menus: "ul", - position: { - my: "left top", - at: "right top" - }, - role: "menu", - - // callbacks - blur: null, - focus: null, - select: null - }, - - _create: function() { - this.activeMenu = this.element; - this.element - .uniqueId() - .addClass( "ui-menu ui-widget ui-widget-content ui-corner-all" ) - .toggleClass( "ui-menu-icons", !!this.element.find( ".ui-icon" ).length ) - .attr({ - role: this.options.role, - tabIndex: 0 - }) - // need to catch all clicks on disabled menu - // not possible through _on - .bind( "click" + this.eventNamespace, $.proxy(function( event ) { - if ( this.options.disabled ) { - event.preventDefault(); - } - }, this )); - - if ( this.options.disabled ) { - this.element - .addClass( "ui-state-disabled" ) - .attr( "aria-disabled", "true" ); - } - - this._on({ - // Prevent focus from sticking to links inside menu after clicking - // them (focus should always stay on UL during navigation). - "mousedown .ui-menu-item > a": function( event ) { - event.preventDefault(); - }, - "click .ui-state-disabled > a": function( event ) { - event.preventDefault(); - }, - "click .ui-menu-item:has(a)": function( event ) { - var target = $( event.target ).closest( ".ui-menu-item" ); - if ( !mouseHandled && target.not( ".ui-state-disabled" ).length ) { - mouseHandled = true; - - this.select( event ); - // Open submenu on click - if ( target.has( ".ui-menu" ).length ) { - this.expand( event ); - } else if ( !this.element.is( ":focus" ) ) { - // Redirect focus to the menu - this.element.trigger( "focus", [ true ] ); - - // If the active item is on the top level, let it stay active. - // Otherwise, blur the active item since it is no longer visible. - if ( this.active && this.active.parents( ".ui-menu" ).length === 1 ) { - clearTimeout( this.timer ); - } - } - } - }, - "mouseenter .ui-menu-item": function( event ) { - var target = $( event.currentTarget ); - // Remove ui-state-active class from siblings of the newly focused menu item - // to avoid a jump caused by adjacent elements both having a class with a border - target.siblings().children( ".ui-state-active" ).removeClass( "ui-state-active" ); - this.focus( event, target ); - }, - mouseleave: "collapseAll", - "mouseleave .ui-menu": "collapseAll", - focus: function( event, keepActiveItem ) { - // If there's already an active item, keep it active - // If not, activate the first item - var item = this.active || this.element.children( ".ui-menu-item" ).eq( 0 ); - - if ( !keepActiveItem ) { - this.focus( event, item ); - } - }, - blur: function( event ) { - this._delay(function() { - if ( !$.contains( this.element[0], this.document[0].activeElement ) ) { - this.collapseAll( event ); - } - }); - }, - keydown: "_keydown" - }); - - this.refresh(); - - // Clicks outside of a menu collapse any open menus - this._on( this.document, { - click: function( event ) { - if ( !$( event.target ).closest( ".ui-menu" ).length ) { - this.collapseAll( event ); - } - - // Reset the mouseHandled flag - mouseHandled = false; - } - }); - }, - - _destroy: function() { - // Destroy (sub)menus - this.element - .removeAttr( "aria-activedescendant" ) - .find( ".ui-menu" ).andSelf() - .removeClass( "ui-menu ui-widget ui-widget-content ui-corner-all ui-menu-icons" ) - .removeAttr( "role" ) - .removeAttr( "tabIndex" ) - .removeAttr( "aria-labelledby" ) - .removeAttr( "aria-expanded" ) - .removeAttr( "aria-hidden" ) - .removeAttr( "aria-disabled" ) - .removeUniqueId() - .show(); - - // Destroy menu items - this.element.find( ".ui-menu-item" ) - .removeClass( "ui-menu-item" ) - .removeAttr( "role" ) - .removeAttr( "aria-disabled" ) - .children( "a" ) - .removeUniqueId() - .removeClass( "ui-corner-all ui-state-hover" ) - .removeAttr( "tabIndex" ) - .removeAttr( "role" ) - .removeAttr( "aria-haspopup" ) - .children().each( function() { - var elem = $( this ); - if ( elem.data( "ui-menu-submenu-carat" ) ) { - elem.remove(); - } - }); - - // Destroy menu dividers - this.element.find( ".ui-menu-divider" ).removeClass( "ui-menu-divider ui-widget-content" ); - }, - - _keydown: function( event ) { - var match, prev, character, skip, regex, - preventDefault = true; - - function escape( value ) { - return value.replace( /[\-\[\]{}()*+?.,\\\^$|#\s]/g, "\\$&" ); - } - - switch ( event.keyCode ) { - case $.ui.keyCode.PAGE_UP: - this.previousPage( event ); - break; - case $.ui.keyCode.PAGE_DOWN: - this.nextPage( event ); - break; - case $.ui.keyCode.HOME: - this._move( "first", "first", event ); - break; - case $.ui.keyCode.END: - this._move( "last", "last", event ); - break; - case $.ui.keyCode.UP: - this.previous( event ); - break; - case $.ui.keyCode.DOWN: - this.next( event ); - break; - case $.ui.keyCode.LEFT: - this.collapse( event ); - break; - case $.ui.keyCode.RIGHT: - if ( this.active && !this.active.is( ".ui-state-disabled" ) ) { - this.expand( event ); - } - break; - case $.ui.keyCode.ENTER: - case $.ui.keyCode.SPACE: - this._activate( event ); - break; - case $.ui.keyCode.ESCAPE: - this.collapse( event ); - break; - default: - preventDefault = false; - prev = this.previousFilter || ""; - character = String.fromCharCode( event.keyCode ); - skip = false; - - clearTimeout( this.filterTimer ); - - if ( character === prev ) { - skip = true; - } else { - character = prev + character; - } - - regex = new RegExp( "^" + escape( character ), "i" ); - match = this.activeMenu.children( ".ui-menu-item" ).filter(function() { - return regex.test( $( this ).children( "a" ).text() ); - }); - match = skip && match.index( this.active.next() ) !== -1 ? - this.active.nextAll( ".ui-menu-item" ) : - match; - - // If no matches on the current filter, reset to the last character pressed - // to move down the menu to the first item that starts with that character - if ( !match.length ) { - character = String.fromCharCode( event.keyCode ); - regex = new RegExp( "^" + escape( character ), "i" ); - match = this.activeMenu.children( ".ui-menu-item" ).filter(function() { - return regex.test( $( this ).children( "a" ).text() ); - }); - } - - if ( match.length ) { - this.focus( event, match ); - if ( match.length > 1 ) { - this.previousFilter = character; - this.filterTimer = this._delay(function() { - delete this.previousFilter; - }, 1000 ); - } else { - delete this.previousFilter; - } - } else { - delete this.previousFilter; - } - } - - if ( preventDefault ) { - event.preventDefault(); - } - }, - - _activate: function( event ) { - if ( !this.active.is( ".ui-state-disabled" ) ) { - if ( this.active.children( "a[aria-haspopup='true']" ).length ) { - this.expand( event ); - } else { - this.select( event ); - } - } - }, - - refresh: function() { - var menus, - icon = this.options.icons.submenu, - submenus = this.element.find( this.options.menus ); - - // Initialize nested menus - submenus.filter( ":not(.ui-menu)" ) - .addClass( "ui-menu ui-widget ui-widget-content ui-corner-all" ) - .hide() - .attr({ - role: this.options.role, - "aria-hidden": "true", - "aria-expanded": "false" - }) - .each(function() { - var menu = $( this ), - item = menu.prev( "a" ), - submenuCarat = $( "" ) - .addClass( "ui-menu-icon ui-icon " + icon ) - .data( "ui-menu-submenu-carat", true ); - - item - .attr( "aria-haspopup", "true" ) - .prepend( submenuCarat ); - menu.attr( "aria-labelledby", item.attr( "id" ) ); - }); - - menus = submenus.add( this.element ); - - // Don't refresh list items that are already adapted - menus.children( ":not(.ui-menu-item):has(a)" ) - .addClass( "ui-menu-item" ) - .attr( "role", "presentation" ) - .children( "a" ) - .uniqueId() - .addClass( "ui-corner-all" ) - .attr({ - tabIndex: -1, - role: this._itemRole() - }); - - // Initialize unlinked menu-items containing spaces and/or dashes only as dividers - menus.children( ":not(.ui-menu-item)" ).each(function() { - var item = $( this ); - // hyphen, em dash, en dash - if ( !/[^\-—–\s]/.test( item.text() ) ) { - item.addClass( "ui-widget-content ui-menu-divider" ); - } - }); - - // Add aria-disabled attribute to any disabled menu item - menus.children( ".ui-state-disabled" ).attr( "aria-disabled", "true" ); - - // If the active item has been removed, blur the menu - if ( this.active && !$.contains( this.element[ 0 ], this.active[ 0 ] ) ) { - this.blur(); - } - }, - - _itemRole: function() { - return { - menu: "menuitem", - listbox: "option" - }[ this.options.role ]; - }, - - focus: function( event, item ) { - var nested, focused; - this.blur( event, event && event.type === "focus" ); - - this._scrollIntoView( item ); - - this.active = item.first(); - focused = this.active.children( "a" ).addClass( "ui-state-focus" ); - // Only update aria-activedescendant if there's a role - // otherwise we assume focus is managed elsewhere - if ( this.options.role ) { - this.element.attr( "aria-activedescendant", focused.attr( "id" ) ); - } - - // Highlight active parent menu item, if any - this.active - .parent() - .closest( ".ui-menu-item" ) - .children( "a:first" ) - .addClass( "ui-state-active" ); - - if ( event && event.type === "keydown" ) { - this._close(); - } else { - this.timer = this._delay(function() { - this._close(); - }, this.delay ); - } - - nested = item.children( ".ui-menu" ); - if ( nested.length && ( /^mouse/.test( event.type ) ) ) { - this._startOpening(nested); - } - this.activeMenu = item.parent(); - - this._trigger( "focus", event, { item: item } ); - }, - - _scrollIntoView: function( item ) { - var borderTop, paddingTop, offset, scroll, elementHeight, itemHeight; - if ( this._hasScroll() ) { - borderTop = parseFloat( $.css( this.activeMenu[0], "borderTopWidth" ) ) || 0; - paddingTop = parseFloat( $.css( this.activeMenu[0], "paddingTop" ) ) || 0; - offset = item.offset().top - this.activeMenu.offset().top - borderTop - paddingTop; - scroll = this.activeMenu.scrollTop(); - elementHeight = this.activeMenu.height(); - itemHeight = item.height(); - - if ( offset < 0 ) { - this.activeMenu.scrollTop( scroll + offset ); - } else if ( offset + itemHeight > elementHeight ) { - this.activeMenu.scrollTop( scroll + offset - elementHeight + itemHeight ); - } - } - }, - - blur: function( event, fromFocus ) { - if ( !fromFocus ) { - clearTimeout( this.timer ); - } - - if ( !this.active ) { - return; - } - - this.active.children( "a" ).removeClass( "ui-state-focus" ); - this.active = null; - - this._trigger( "blur", event, { item: this.active } ); - }, - - _startOpening: function( submenu ) { - clearTimeout( this.timer ); - - // Don't open if already open fixes a Firefox bug that caused a .5 pixel - // shift in the submenu position when mousing over the carat icon - if ( submenu.attr( "aria-hidden" ) !== "true" ) { - return; - } - - this.timer = this._delay(function() { - this._close(); - this._open( submenu ); - }, this.delay ); - }, - - _open: function( submenu ) { - var position = $.extend({ - of: this.active - }, this.options.position ); - - clearTimeout( this.timer ); - this.element.find( ".ui-menu" ).not( submenu.parents( ".ui-menu" ) ) - .hide() - .attr( "aria-hidden", "true" ); - - submenu - .show() - .removeAttr( "aria-hidden" ) - .attr( "aria-expanded", "true" ) - .position( position ); - }, - - collapseAll: function( event, all ) { - clearTimeout( this.timer ); - this.timer = this._delay(function() { - // If we were passed an event, look for the submenu that contains the event - var currentMenu = all ? this.element : - $( event && event.target ).closest( this.element.find( ".ui-menu" ) ); - - // If we found no valid submenu ancestor, use the main menu to close all sub menus anyway - if ( !currentMenu.length ) { - currentMenu = this.element; - } - - this._close( currentMenu ); - - this.blur( event ); - this.activeMenu = currentMenu; - }, this.delay ); - }, - - // With no arguments, closes the currently active menu - if nothing is active - // it closes all menus. If passed an argument, it will search for menus BELOW - _close: function( startMenu ) { - if ( !startMenu ) { - startMenu = this.active ? this.active.parent() : this.element; - } - - startMenu - .find( ".ui-menu" ) - .hide() - .attr( "aria-hidden", "true" ) - .attr( "aria-expanded", "false" ) - .end() - .find( "a.ui-state-active" ) - .removeClass( "ui-state-active" ); - }, - - collapse: function( event ) { - var newItem = this.active && - this.active.parent().closest( ".ui-menu-item", this.element ); - if ( newItem && newItem.length ) { - this._close(); - this.focus( event, newItem ); - } - }, - - expand: function( event ) { - var newItem = this.active && - this.active - .children( ".ui-menu " ) - .children( ".ui-menu-item" ) - .first(); - - if ( newItem && newItem.length ) { - this._open( newItem.parent() ); - - // Delay so Firefox will not hide activedescendant change in expanding submenu from AT - this._delay(function() { - this.focus( event, newItem ); - }); - } - }, - - next: function( event ) { - this._move( "next", "first", event ); - }, - - previous: function( event ) { - this._move( "prev", "last", event ); - }, - - isFirstItem: function() { - return this.active && !this.active.prevAll( ".ui-menu-item" ).length; - }, - - isLastItem: function() { - return this.active && !this.active.nextAll( ".ui-menu-item" ).length; - }, - - _move: function( direction, filter, event ) { - var next; - if ( this.active ) { - if ( direction === "first" || direction === "last" ) { - next = this.active - [ direction === "first" ? "prevAll" : "nextAll" ]( ".ui-menu-item" ) - .eq( -1 ); - } else { - next = this.active - [ direction + "All" ]( ".ui-menu-item" ) - .eq( 0 ); - } - } - if ( !next || !next.length || !this.active ) { - next = this.activeMenu.children( ".ui-menu-item" )[ filter ](); - } - - this.focus( event, next ); - }, - - nextPage: function( event ) { - var item, base, height; - - if ( !this.active ) { - this.next( event ); - return; - } - if ( this.isLastItem() ) { - return; - } - if ( this._hasScroll() ) { - base = this.active.offset().top; - height = this.element.height(); - this.active.nextAll( ".ui-menu-item" ).each(function() { - item = $( this ); - return item.offset().top - base - height < 0; - }); - - this.focus( event, item ); - } else { - this.focus( event, this.activeMenu.children( ".ui-menu-item" ) - [ !this.active ? "first" : "last" ]() ); - } - }, - - previousPage: function( event ) { - var item, base, height; - if ( !this.active ) { - this.next( event ); - return; - } - if ( this.isFirstItem() ) { - return; - } - if ( this._hasScroll() ) { - base = this.active.offset().top; - height = this.element.height(); - this.active.prevAll( ".ui-menu-item" ).each(function() { - item = $( this ); - return item.offset().top - base + height > 0; - }); - - this.focus( event, item ); - } else { - this.focus( event, this.activeMenu.children( ".ui-menu-item" ).first() ); - } - }, - - _hasScroll: function() { - return this.element.outerHeight() < this.element.prop( "scrollHeight" ); - }, - - select: function( event ) { - // TODO: It should never be possible to not have an active item at this - // point, but the tests don't trigger mouseenter before click. - this.active = this.active || $( event.target ).closest( ".ui-menu-item" ); - var ui = { item: this.active }; - if ( !this.active.has( ".ui-menu" ).length ) { - this.collapseAll( event, true ); - } - this._trigger( "select", event, ui ); - } -}); - -}( jQuery )); - -(function( $, undefined ) { - -$.ui = $.ui || {}; - -var cachedScrollbarWidth, - max = Math.max, - abs = Math.abs, - round = Math.round, - rhorizontal = /left|center|right/, - rvertical = /top|center|bottom/, - roffset = /[\+\-]\d+%?/, - rposition = /^\w+/, - rpercent = /%$/, - _position = $.fn.position; - -function getOffsets( offsets, width, height ) { - return [ - parseInt( offsets[ 0 ], 10 ) * ( rpercent.test( offsets[ 0 ] ) ? width / 100 : 1 ), - parseInt( offsets[ 1 ], 10 ) * ( rpercent.test( offsets[ 1 ] ) ? height / 100 : 1 ) - ]; -} -function parseCss( element, property ) { - return parseInt( $.css( element, property ), 10 ) || 0; -} - -$.position = { - scrollbarWidth: function() { - if ( cachedScrollbarWidth !== undefined ) { - return cachedScrollbarWidth; - } - var w1, w2, - div = $( "
    " ), - innerDiv = div.children()[0]; - - $( "body" ).append( div ); - w1 = innerDiv.offsetWidth; - div.css( "overflow", "scroll" ); - - w2 = innerDiv.offsetWidth; - - if ( w1 === w2 ) { - w2 = div[0].clientWidth; - } - - div.remove(); - - return (cachedScrollbarWidth = w1 - w2); - }, - getScrollInfo: function( within ) { - var overflowX = within.isWindow ? "" : within.element.css( "overflow-x" ), - overflowY = within.isWindow ? "" : within.element.css( "overflow-y" ), - hasOverflowX = overflowX === "scroll" || - ( overflowX === "auto" && within.width < within.element[0].scrollWidth ), - hasOverflowY = overflowY === "scroll" || - ( overflowY === "auto" && within.height < within.element[0].scrollHeight ); - return { - width: hasOverflowX ? $.position.scrollbarWidth() : 0, - height: hasOverflowY ? $.position.scrollbarWidth() : 0 - }; - }, - getWithinInfo: function( element ) { - var withinElement = $( element || window ), - isWindow = $.isWindow( withinElement[0] ); - return { - element: withinElement, - isWindow: isWindow, - offset: withinElement.offset() || { left: 0, top: 0 }, - scrollLeft: withinElement.scrollLeft(), - scrollTop: withinElement.scrollTop(), - width: isWindow ? withinElement.width() : withinElement.outerWidth(), - height: isWindow ? withinElement.height() : withinElement.outerHeight() - }; - } -}; - -$.fn.position = function( options ) { - if ( !options || !options.of ) { - return _position.apply( this, arguments ); - } - - // make a copy, we don't want to modify arguments - options = $.extend( {}, options ); - - var atOffset, targetWidth, targetHeight, targetOffset, basePosition, - target = $( options.of ), - within = $.position.getWithinInfo( options.within ), - scrollInfo = $.position.getScrollInfo( within ), - targetElem = target[0], - collision = ( options.collision || "flip" ).split( " " ), - offsets = {}; - - if ( targetElem.nodeType === 9 ) { - targetWidth = target.width(); - targetHeight = target.height(); - targetOffset = { top: 0, left: 0 }; - } else if ( $.isWindow( targetElem ) ) { - targetWidth = target.width(); - targetHeight = target.height(); - targetOffset = { top: target.scrollTop(), left: target.scrollLeft() }; - } else if ( targetElem.preventDefault ) { - // force left top to allow flipping - options.at = "left top"; - targetWidth = targetHeight = 0; - targetOffset = { top: targetElem.pageY, left: targetElem.pageX }; - } else { - targetWidth = target.outerWidth(); - targetHeight = target.outerHeight(); - targetOffset = target.offset(); - } - // clone to reuse original targetOffset later - basePosition = $.extend( {}, targetOffset ); - - // force my and at to have valid horizontal and vertical positions - // if a value is missing or invalid, it will be converted to center - $.each( [ "my", "at" ], function() { - var pos = ( options[ this ] || "" ).split( " " ), - horizontalOffset, - verticalOffset; - - if ( pos.length === 1) { - pos = rhorizontal.test( pos[ 0 ] ) ? - pos.concat( [ "center" ] ) : - rvertical.test( pos[ 0 ] ) ? - [ "center" ].concat( pos ) : - [ "center", "center" ]; - } - pos[ 0 ] = rhorizontal.test( pos[ 0 ] ) ? pos[ 0 ] : "center"; - pos[ 1 ] = rvertical.test( pos[ 1 ] ) ? pos[ 1 ] : "center"; - - // calculate offsets - horizontalOffset = roffset.exec( pos[ 0 ] ); - verticalOffset = roffset.exec( pos[ 1 ] ); - offsets[ this ] = [ - horizontalOffset ? horizontalOffset[ 0 ] : 0, - verticalOffset ? verticalOffset[ 0 ] : 0 - ]; - - // reduce to just the positions without the offsets - options[ this ] = [ - rposition.exec( pos[ 0 ] )[ 0 ], - rposition.exec( pos[ 1 ] )[ 0 ] - ]; - }); - - // normalize collision option - if ( collision.length === 1 ) { - collision[ 1 ] = collision[ 0 ]; - } - - if ( options.at[ 0 ] === "right" ) { - basePosition.left += targetWidth; - } else if ( options.at[ 0 ] === "center" ) { - basePosition.left += targetWidth / 2; - } - - if ( options.at[ 1 ] === "bottom" ) { - basePosition.top += targetHeight; - } else if ( options.at[ 1 ] === "center" ) { - basePosition.top += targetHeight / 2; - } - - atOffset = getOffsets( offsets.at, targetWidth, targetHeight ); - basePosition.left += atOffset[ 0 ]; - basePosition.top += atOffset[ 1 ]; - - return this.each(function() { - var collisionPosition, using, - elem = $( this ), - elemWidth = elem.outerWidth(), - elemHeight = elem.outerHeight(), - marginLeft = parseCss( this, "marginLeft" ), - marginTop = parseCss( this, "marginTop" ), - collisionWidth = elemWidth + marginLeft + parseCss( this, "marginRight" ) + scrollInfo.width, - collisionHeight = elemHeight + marginTop + parseCss( this, "marginBottom" ) + scrollInfo.height, - position = $.extend( {}, basePosition ), - myOffset = getOffsets( offsets.my, elem.outerWidth(), elem.outerHeight() ); - - if ( options.my[ 0 ] === "right" ) { - position.left -= elemWidth; - } else if ( options.my[ 0 ] === "center" ) { - position.left -= elemWidth / 2; - } - - if ( options.my[ 1 ] === "bottom" ) { - position.top -= elemHeight; - } else if ( options.my[ 1 ] === "center" ) { - position.top -= elemHeight / 2; - } - - position.left += myOffset[ 0 ]; - position.top += myOffset[ 1 ]; - - // if the browser doesn't support fractions, then round for consistent results - if ( !$.support.offsetFractions ) { - position.left = round( position.left ); - position.top = round( position.top ); - } - - collisionPosition = { - marginLeft: marginLeft, - marginTop: marginTop - }; - - $.each( [ "left", "top" ], function( i, dir ) { - if ( $.ui.position[ collision[ i ] ] ) { - $.ui.position[ collision[ i ] ][ dir ]( position, { - targetWidth: targetWidth, - targetHeight: targetHeight, - elemWidth: elemWidth, - elemHeight: elemHeight, - collisionPosition: collisionPosition, - collisionWidth: collisionWidth, - collisionHeight: collisionHeight, - offset: [ atOffset[ 0 ] + myOffset[ 0 ], atOffset [ 1 ] + myOffset[ 1 ] ], - my: options.my, - at: options.at, - within: within, - elem : elem - }); - } - }); - - if ( $.fn.bgiframe ) { - elem.bgiframe(); - } - - if ( options.using ) { - // adds feedback as second argument to using callback, if present - using = function( props ) { - var left = targetOffset.left - position.left, - right = left + targetWidth - elemWidth, - top = targetOffset.top - position.top, - bottom = top + targetHeight - elemHeight, - feedback = { - target: { - element: target, - left: targetOffset.left, - top: targetOffset.top, - width: targetWidth, - height: targetHeight - }, - element: { - element: elem, - left: position.left, - top: position.top, - width: elemWidth, - height: elemHeight - }, - horizontal: right < 0 ? "left" : left > 0 ? "right" : "center", - vertical: bottom < 0 ? "top" : top > 0 ? "bottom" : "middle" - }; - if ( targetWidth < elemWidth && abs( left + right ) < targetWidth ) { - feedback.horizontal = "center"; - } - if ( targetHeight < elemHeight && abs( top + bottom ) < targetHeight ) { - feedback.vertical = "middle"; - } - if ( max( abs( left ), abs( right ) ) > max( abs( top ), abs( bottom ) ) ) { - feedback.important = "horizontal"; - } else { - feedback.important = "vertical"; - } - options.using.call( this, props, feedback ); - }; - } - - elem.offset( $.extend( position, { using: using } ) ); - }); -}; - -$.ui.position = { - fit: { - left: function( position, data ) { - var within = data.within, - withinOffset = within.isWindow ? within.scrollLeft : within.offset.left, - outerWidth = within.width, - collisionPosLeft = position.left - data.collisionPosition.marginLeft, - overLeft = withinOffset - collisionPosLeft, - overRight = collisionPosLeft + data.collisionWidth - outerWidth - withinOffset, - newOverRight; - - // element is wider than within - if ( data.collisionWidth > outerWidth ) { - // element is initially over the left side of within - if ( overLeft > 0 && overRight <= 0 ) { - newOverRight = position.left + overLeft + data.collisionWidth - outerWidth - withinOffset; - position.left += overLeft - newOverRight; - // element is initially over right side of within - } else if ( overRight > 0 && overLeft <= 0 ) { - position.left = withinOffset; - // element is initially over both left and right sides of within - } else { - if ( overLeft > overRight ) { - position.left = withinOffset + outerWidth - data.collisionWidth; - } else { - position.left = withinOffset; - } - } - // too far left -> align with left edge - } else if ( overLeft > 0 ) { - position.left += overLeft; - // too far right -> align with right edge - } else if ( overRight > 0 ) { - position.left -= overRight; - // adjust based on position and margin - } else { - position.left = max( position.left - collisionPosLeft, position.left ); - } - }, - top: function( position, data ) { - var within = data.within, - withinOffset = within.isWindow ? within.scrollTop : within.offset.top, - outerHeight = data.within.height, - collisionPosTop = position.top - data.collisionPosition.marginTop, - overTop = withinOffset - collisionPosTop, - overBottom = collisionPosTop + data.collisionHeight - outerHeight - withinOffset, - newOverBottom; - - // element is taller than within - if ( data.collisionHeight > outerHeight ) { - // element is initially over the top of within - if ( overTop > 0 && overBottom <= 0 ) { - newOverBottom = position.top + overTop + data.collisionHeight - outerHeight - withinOffset; - position.top += overTop - newOverBottom; - // element is initially over bottom of within - } else if ( overBottom > 0 && overTop <= 0 ) { - position.top = withinOffset; - // element is initially over both top and bottom of within - } else { - if ( overTop > overBottom ) { - position.top = withinOffset + outerHeight - data.collisionHeight; - } else { - position.top = withinOffset; - } - } - // too far up -> align with top - } else if ( overTop > 0 ) { - position.top += overTop; - // too far down -> align with bottom edge - } else if ( overBottom > 0 ) { - position.top -= overBottom; - // adjust based on position and margin - } else { - position.top = max( position.top - collisionPosTop, position.top ); - } - } - }, - flip: { - left: function( position, data ) { - var within = data.within, - withinOffset = within.offset.left + within.scrollLeft, - outerWidth = within.width, - offsetLeft = within.isWindow ? within.scrollLeft : within.offset.left, - collisionPosLeft = position.left - data.collisionPosition.marginLeft, - overLeft = collisionPosLeft - offsetLeft, - overRight = collisionPosLeft + data.collisionWidth - outerWidth - offsetLeft, - myOffset = data.my[ 0 ] === "left" ? - -data.elemWidth : - data.my[ 0 ] === "right" ? - data.elemWidth : - 0, - atOffset = data.at[ 0 ] === "left" ? - data.targetWidth : - data.at[ 0 ] === "right" ? - -data.targetWidth : - 0, - offset = -2 * data.offset[ 0 ], - newOverRight, - newOverLeft; - - if ( overLeft < 0 ) { - newOverRight = position.left + myOffset + atOffset + offset + data.collisionWidth - outerWidth - withinOffset; - if ( newOverRight < 0 || newOverRight < abs( overLeft ) ) { - position.left += myOffset + atOffset + offset; - } - } - else if ( overRight > 0 ) { - newOverLeft = position.left - data.collisionPosition.marginLeft + myOffset + atOffset + offset - offsetLeft; - if ( newOverLeft > 0 || abs( newOverLeft ) < overRight ) { - position.left += myOffset + atOffset + offset; - } - } - }, - top: function( position, data ) { - var within = data.within, - withinOffset = within.offset.top + within.scrollTop, - outerHeight = within.height, - offsetTop = within.isWindow ? within.scrollTop : within.offset.top, - collisionPosTop = position.top - data.collisionPosition.marginTop, - overTop = collisionPosTop - offsetTop, - overBottom = collisionPosTop + data.collisionHeight - outerHeight - offsetTop, - top = data.my[ 1 ] === "top", - myOffset = top ? - -data.elemHeight : - data.my[ 1 ] === "bottom" ? - data.elemHeight : - 0, - atOffset = data.at[ 1 ] === "top" ? - data.targetHeight : - data.at[ 1 ] === "bottom" ? - -data.targetHeight : - 0, - offset = -2 * data.offset[ 1 ], - newOverTop, - newOverBottom; - if ( overTop < 0 ) { - newOverBottom = position.top + myOffset + atOffset + offset + data.collisionHeight - outerHeight - withinOffset; - if ( ( position.top + myOffset + atOffset + offset) > overTop && ( newOverBottom < 0 || newOverBottom < abs( overTop ) ) ) { - position.top += myOffset + atOffset + offset; - } - } - else if ( overBottom > 0 ) { - newOverTop = position.top - data.collisionPosition.marginTop + myOffset + atOffset + offset - offsetTop; - if ( ( position.top + myOffset + atOffset + offset) > overBottom && ( newOverTop > 0 || abs( newOverTop ) < overBottom ) ) { - position.top += myOffset + atOffset + offset; - } - } - } - }, - flipfit: { - left: function() { - $.ui.position.flip.left.apply( this, arguments ); - $.ui.position.fit.left.apply( this, arguments ); - }, - top: function() { - $.ui.position.flip.top.apply( this, arguments ); - $.ui.position.fit.top.apply( this, arguments ); - } - } -}; - -// fraction support test -(function () { - var testElement, testElementParent, testElementStyle, offsetLeft, i, - body = document.getElementsByTagName( "body" )[ 0 ], - div = document.createElement( "div" ); - - //Create a "fake body" for testing based on method used in jQuery.support - testElement = document.createElement( body ? "div" : "body" ); - testElementStyle = { - visibility: "hidden", - width: 0, - height: 0, - border: 0, - margin: 0, - background: "none" - }; - if ( body ) { - $.extend( testElementStyle, { - position: "absolute", - left: "-1000px", - top: "-1000px" - }); - } - for ( i in testElementStyle ) { - testElement.style[ i ] = testElementStyle[ i ]; - } - testElement.appendChild( div ); - testElementParent = body || document.documentElement; - testElementParent.insertBefore( testElement, testElementParent.firstChild ); - - div.style.cssText = "position: absolute; left: 10.7432222px;"; - - offsetLeft = $( div ).offset().left; - $.support.offsetFractions = offsetLeft > 10 && offsetLeft < 11; - - testElement.innerHTML = ""; - testElementParent.removeChild( testElement ); -})(); - -// DEPRECATED -if ( $.uiBackCompat !== false ) { - // offset option - (function( $ ) { - var _position = $.fn.position; - $.fn.position = function( options ) { - if ( !options || !options.offset ) { - return _position.call( this, options ); - } - var offset = options.offset.split( " " ), - at = options.at.split( " " ); - if ( offset.length === 1 ) { - offset[ 1 ] = offset[ 0 ]; - } - if ( /^\d/.test( offset[ 0 ] ) ) { - offset[ 0 ] = "+" + offset[ 0 ]; - } - if ( /^\d/.test( offset[ 1 ] ) ) { - offset[ 1 ] = "+" + offset[ 1 ]; - } - if ( at.length === 1 ) { - if ( /left|center|right/.test( at[ 0 ] ) ) { - at[ 1 ] = "center"; - } else { - at[ 1 ] = at[ 0 ]; - at[ 0 ] = "center"; - } - } - return _position.call( this, $.extend( options, { - at: at[ 0 ] + offset[ 0 ] + " " + at[ 1 ] + offset[ 1 ], - offset: undefined - } ) ); - }; - }( jQuery ) ); -} - -}( jQuery ) ); - -(function( $, undefined ) { - -$.widget( "ui.progressbar", { - version: "1.9.2", - options: { - value: 0, - max: 100 - }, - - min: 0, - - _create: function() { - this.element - .addClass( "ui-progressbar ui-widget ui-widget-content ui-corner-all" ) - .attr({ - role: "progressbar", - "aria-valuemin": this.min, - "aria-valuemax": this.options.max, - "aria-valuenow": this._value() - }); - - this.valueDiv = $( "
    " ) - .appendTo( this.element ); - - this.oldValue = this._value(); - this._refreshValue(); - }, - - _destroy: function() { - this.element - .removeClass( "ui-progressbar ui-widget ui-widget-content ui-corner-all" ) - .removeAttr( "role" ) - .removeAttr( "aria-valuemin" ) - .removeAttr( "aria-valuemax" ) - .removeAttr( "aria-valuenow" ); - - this.valueDiv.remove(); - }, - - value: function( newValue ) { - if ( newValue === undefined ) { - return this._value(); - } - - this._setOption( "value", newValue ); - return this; - }, - - _setOption: function( key, value ) { - if ( key === "value" ) { - this.options.value = value; - this._refreshValue(); - if ( this._value() === this.options.max ) { - this._trigger( "complete" ); - } - } - - this._super( key, value ); - }, - - _value: function() { - var val = this.options.value; - // normalize invalid value - if ( typeof val !== "number" ) { - val = 0; - } - return Math.min( this.options.max, Math.max( this.min, val ) ); - }, - - _percentage: function() { - return 100 * this._value() / this.options.max; - }, - - _refreshValue: function() { - var value = this.value(), - percentage = this._percentage(); - - if ( this.oldValue !== value ) { - this.oldValue = value; - this._trigger( "change" ); - } - - this.valueDiv - .toggle( value > this.min ) - .toggleClass( "ui-corner-right", value === this.options.max ) - .width( percentage.toFixed(0) + "%" ); - this.element.attr( "aria-valuenow", value ); - } -}); - -})( jQuery ); - -(function( $, undefined ) { - -// number of pages in a slider -// (how many times can you page up/down to go through the whole range) -var numPages = 5; - -$.widget( "ui.slider", $.ui.mouse, { - version: "1.9.2", - widgetEventPrefix: "slide", - - options: { - animate: false, - distance: 0, - max: 100, - min: 0, - orientation: "horizontal", - range: false, - step: 1, - value: 0, - values: null - }, - - _create: function() { - var i, handleCount, - o = this.options, - existingHandles = this.element.find( ".ui-slider-handle" ).addClass( "ui-state-default ui-corner-all" ), - handle = "", - handles = []; - - this._keySliding = false; - this._mouseSliding = false; - this._animateOff = true; - this._handleIndex = null; - this._detectOrientation(); - this._mouseInit(); - - this.element - .addClass( "ui-slider" + - " ui-slider-" + this.orientation + - " ui-widget" + - " ui-widget-content" + - " ui-corner-all" + - ( o.disabled ? " ui-slider-disabled ui-disabled" : "" ) ); - - this.range = $([]); - - if ( o.range ) { - if ( o.range === true ) { - if ( !o.values ) { - o.values = [ this._valueMin(), this._valueMin() ]; - } - if ( o.values.length && o.values.length !== 2 ) { - o.values = [ o.values[0], o.values[0] ]; - } - } - - this.range = $( "
    " ) - .appendTo( this.element ) - .addClass( "ui-slider-range" + - // note: this isn't the most fittingly semantic framework class for this element, - // but worked best visually with a variety of themes - " ui-widget-header" + - ( ( o.range === "min" || o.range === "max" ) ? " ui-slider-range-" + o.range : "" ) ); - } - - handleCount = ( o.values && o.values.length ) || 1; - - for ( i = existingHandles.length; i < handleCount; i++ ) { - handles.push( handle ); - } - - this.handles = existingHandles.add( $( handles.join( "" ) ).appendTo( this.element ) ); - - this.handle = this.handles.eq( 0 ); - - this.handles.add( this.range ).filter( "a" ) - .click(function( event ) { - event.preventDefault(); - }) - .mouseenter(function() { - if ( !o.disabled ) { - $( this ).addClass( "ui-state-hover" ); - } - }) - .mouseleave(function() { - $( this ).removeClass( "ui-state-hover" ); - }) - .focus(function() { - if ( !o.disabled ) { - $( ".ui-slider .ui-state-focus" ).removeClass( "ui-state-focus" ); - $( this ).addClass( "ui-state-focus" ); - } else { - $( this ).blur(); - } - }) - .blur(function() { - $( this ).removeClass( "ui-state-focus" ); - }); - - this.handles.each(function( i ) { - $( this ).data( "ui-slider-handle-index", i ); - }); - - this._on( this.handles, { - keydown: function( event ) { - var allowed, curVal, newVal, step, - index = $( event.target ).data( "ui-slider-handle-index" ); - - switch ( event.keyCode ) { - case $.ui.keyCode.HOME: - case $.ui.keyCode.END: - case $.ui.keyCode.PAGE_UP: - case $.ui.keyCode.PAGE_DOWN: - case $.ui.keyCode.UP: - case $.ui.keyCode.RIGHT: - case $.ui.keyCode.DOWN: - case $.ui.keyCode.LEFT: - event.preventDefault(); - if ( !this._keySliding ) { - this._keySliding = true; - $( event.target ).addClass( "ui-state-active" ); - allowed = this._start( event, index ); - if ( allowed === false ) { - return; - } - } - break; - } - - step = this.options.step; - if ( this.options.values && this.options.values.length ) { - curVal = newVal = this.values( index ); - } else { - curVal = newVal = this.value(); - } - - switch ( event.keyCode ) { - case $.ui.keyCode.HOME: - newVal = this._valueMin(); - break; - case $.ui.keyCode.END: - newVal = this._valueMax(); - break; - case $.ui.keyCode.PAGE_UP: - newVal = this._trimAlignValue( curVal + ( (this._valueMax() - this._valueMin()) / numPages ) ); - break; - case $.ui.keyCode.PAGE_DOWN: - newVal = this._trimAlignValue( curVal - ( (this._valueMax() - this._valueMin()) / numPages ) ); - break; - case $.ui.keyCode.UP: - case $.ui.keyCode.RIGHT: - if ( curVal === this._valueMax() ) { - return; - } - newVal = this._trimAlignValue( curVal + step ); - break; - case $.ui.keyCode.DOWN: - case $.ui.keyCode.LEFT: - if ( curVal === this._valueMin() ) { - return; - } - newVal = this._trimAlignValue( curVal - step ); - break; - } - - this._slide( event, index, newVal ); - }, - keyup: function( event ) { - var index = $( event.target ).data( "ui-slider-handle-index" ); - - if ( this._keySliding ) { - this._keySliding = false; - this._stop( event, index ); - this._change( event, index ); - $( event.target ).removeClass( "ui-state-active" ); - } - } - }); - - this._refreshValue(); - - this._animateOff = false; - }, - - _destroy: function() { - this.handles.remove(); - this.range.remove(); - - this.element - .removeClass( "ui-slider" + - " ui-slider-horizontal" + - " ui-slider-vertical" + - " ui-slider-disabled" + - " ui-widget" + - " ui-widget-content" + - " ui-corner-all" ); - - this._mouseDestroy(); - }, - - _mouseCapture: function( event ) { - var position, normValue, distance, closestHandle, index, allowed, offset, mouseOverHandle, - that = this, - o = this.options; - - if ( o.disabled ) { - return false; - } - - this.elementSize = { - width: this.element.outerWidth(), - height: this.element.outerHeight() - }; - this.elementOffset = this.element.offset(); - - position = { x: event.pageX, y: event.pageY }; - normValue = this._normValueFromMouse( position ); - distance = this._valueMax() - this._valueMin() + 1; - this.handles.each(function( i ) { - var thisDistance = Math.abs( normValue - that.values(i) ); - if ( distance > thisDistance ) { - distance = thisDistance; - closestHandle = $( this ); - index = i; - } - }); - - // workaround for bug #3736 (if both handles of a range are at 0, - // the first is always used as the one with least distance, - // and moving it is obviously prevented by preventing negative ranges) - if( o.range === true && this.values(1) === o.min ) { - index += 1; - closestHandle = $( this.handles[index] ); - } - - allowed = this._start( event, index ); - if ( allowed === false ) { - return false; - } - this._mouseSliding = true; - - this._handleIndex = index; - - closestHandle - .addClass( "ui-state-active" ) - .focus(); - - offset = closestHandle.offset(); - mouseOverHandle = !$( event.target ).parents().andSelf().is( ".ui-slider-handle" ); - this._clickOffset = mouseOverHandle ? { left: 0, top: 0 } : { - left: event.pageX - offset.left - ( closestHandle.width() / 2 ), - top: event.pageY - offset.top - - ( closestHandle.height() / 2 ) - - ( parseInt( closestHandle.css("borderTopWidth"), 10 ) || 0 ) - - ( parseInt( closestHandle.css("borderBottomWidth"), 10 ) || 0) + - ( parseInt( closestHandle.css("marginTop"), 10 ) || 0) - }; - - if ( !this.handles.hasClass( "ui-state-hover" ) ) { - this._slide( event, index, normValue ); - } - this._animateOff = true; - return true; - }, - - _mouseStart: function() { - return true; - }, - - _mouseDrag: function( event ) { - var position = { x: event.pageX, y: event.pageY }, - normValue = this._normValueFromMouse( position ); - - this._slide( event, this._handleIndex, normValue ); - - return false; - }, - - _mouseStop: function( event ) { - this.handles.removeClass( "ui-state-active" ); - this._mouseSliding = false; - - this._stop( event, this._handleIndex ); - this._change( event, this._handleIndex ); - - this._handleIndex = null; - this._clickOffset = null; - this._animateOff = false; - - return false; - }, - - _detectOrientation: function() { - this.orientation = ( this.options.orientation === "vertical" ) ? "vertical" : "horizontal"; - }, - - _normValueFromMouse: function( position ) { - var pixelTotal, - pixelMouse, - percentMouse, - valueTotal, - valueMouse; - - if ( this.orientation === "horizontal" ) { - pixelTotal = this.elementSize.width; - pixelMouse = position.x - this.elementOffset.left - ( this._clickOffset ? this._clickOffset.left : 0 ); - } else { - pixelTotal = this.elementSize.height; - pixelMouse = position.y - this.elementOffset.top - ( this._clickOffset ? this._clickOffset.top : 0 ); - } - - percentMouse = ( pixelMouse / pixelTotal ); - if ( percentMouse > 1 ) { - percentMouse = 1; - } - if ( percentMouse < 0 ) { - percentMouse = 0; - } - if ( this.orientation === "vertical" ) { - percentMouse = 1 - percentMouse; - } - - valueTotal = this._valueMax() - this._valueMin(); - valueMouse = this._valueMin() + percentMouse * valueTotal; - - return this._trimAlignValue( valueMouse ); - }, - - _start: function( event, index ) { - var uiHash = { - handle: this.handles[ index ], - value: this.value() - }; - if ( this.options.values && this.options.values.length ) { - uiHash.value = this.values( index ); - uiHash.values = this.values(); - } - return this._trigger( "start", event, uiHash ); - }, - - _slide: function( event, index, newVal ) { - var otherVal, - newValues, - allowed; - - if ( this.options.values && this.options.values.length ) { - otherVal = this.values( index ? 0 : 1 ); - - if ( ( this.options.values.length === 2 && this.options.range === true ) && - ( ( index === 0 && newVal > otherVal) || ( index === 1 && newVal < otherVal ) ) - ) { - newVal = otherVal; - } - - if ( newVal !== this.values( index ) ) { - newValues = this.values(); - newValues[ index ] = newVal; - // A slide can be canceled by returning false from the slide callback - allowed = this._trigger( "slide", event, { - handle: this.handles[ index ], - value: newVal, - values: newValues - } ); - otherVal = this.values( index ? 0 : 1 ); - if ( allowed !== false ) { - this.values( index, newVal, true ); - } - } - } else { - if ( newVal !== this.value() ) { - // A slide can be canceled by returning false from the slide callback - allowed = this._trigger( "slide", event, { - handle: this.handles[ index ], - value: newVal - } ); - if ( allowed !== false ) { - this.value( newVal ); - } - } - } - }, - - _stop: function( event, index ) { - var uiHash = { - handle: this.handles[ index ], - value: this.value() - }; - if ( this.options.values && this.options.values.length ) { - uiHash.value = this.values( index ); - uiHash.values = this.values(); - } - - this._trigger( "stop", event, uiHash ); - }, - - _change: function( event, index ) { - if ( !this._keySliding && !this._mouseSliding ) { - var uiHash = { - handle: this.handles[ index ], - value: this.value() - }; - if ( this.options.values && this.options.values.length ) { - uiHash.value = this.values( index ); - uiHash.values = this.values(); - } - - this._trigger( "change", event, uiHash ); - } - }, - - value: function( newValue ) { - if ( arguments.length ) { - this.options.value = this._trimAlignValue( newValue ); - this._refreshValue(); - this._change( null, 0 ); - return; - } - - return this._value(); - }, - - values: function( index, newValue ) { - var vals, - newValues, - i; - - if ( arguments.length > 1 ) { - this.options.values[ index ] = this._trimAlignValue( newValue ); - this._refreshValue(); - this._change( null, index ); - return; - } - - if ( arguments.length ) { - if ( $.isArray( arguments[ 0 ] ) ) { - vals = this.options.values; - newValues = arguments[ 0 ]; - for ( i = 0; i < vals.length; i += 1 ) { - vals[ i ] = this._trimAlignValue( newValues[ i ] ); - this._change( null, i ); - } - this._refreshValue(); - } else { - if ( this.options.values && this.options.values.length ) { - return this._values( index ); - } else { - return this.value(); - } - } - } else { - return this._values(); - } - }, - - _setOption: function( key, value ) { - var i, - valsLength = 0; - - if ( $.isArray( this.options.values ) ) { - valsLength = this.options.values.length; - } - - $.Widget.prototype._setOption.apply( this, arguments ); - - switch ( key ) { - case "disabled": - if ( value ) { - this.handles.filter( ".ui-state-focus" ).blur(); - this.handles.removeClass( "ui-state-hover" ); - this.handles.prop( "disabled", true ); - this.element.addClass( "ui-disabled" ); - } else { - this.handles.prop( "disabled", false ); - this.element.removeClass( "ui-disabled" ); - } - break; - case "orientation": - this._detectOrientation(); - this.element - .removeClass( "ui-slider-horizontal ui-slider-vertical" ) - .addClass( "ui-slider-" + this.orientation ); - this._refreshValue(); - break; - case "value": - this._animateOff = true; - this._refreshValue(); - this._change( null, 0 ); - this._animateOff = false; - break; - case "values": - this._animateOff = true; - this._refreshValue(); - for ( i = 0; i < valsLength; i += 1 ) { - this._change( null, i ); - } - this._animateOff = false; - break; - case "min": - case "max": - this._animateOff = true; - this._refreshValue(); - this._animateOff = false; - break; - } - }, - - //internal value getter - // _value() returns value trimmed by min and max, aligned by step - _value: function() { - var val = this.options.value; - val = this._trimAlignValue( val ); - - return val; - }, - - //internal values getter - // _values() returns array of values trimmed by min and max, aligned by step - // _values( index ) returns single value trimmed by min and max, aligned by step - _values: function( index ) { - var val, - vals, - i; - - if ( arguments.length ) { - val = this.options.values[ index ]; - val = this._trimAlignValue( val ); - - return val; - } else { - // .slice() creates a copy of the array - // this copy gets trimmed by min and max and then returned - vals = this.options.values.slice(); - for ( i = 0; i < vals.length; i+= 1) { - vals[ i ] = this._trimAlignValue( vals[ i ] ); - } - - return vals; - } - }, - - // returns the step-aligned value that val is closest to, between (inclusive) min and max - _trimAlignValue: function( val ) { - if ( val <= this._valueMin() ) { - return this._valueMin(); - } - if ( val >= this._valueMax() ) { - return this._valueMax(); - } - var step = ( this.options.step > 0 ) ? this.options.step : 1, - valModStep = (val - this._valueMin()) % step, - alignValue = val - valModStep; - - if ( Math.abs(valModStep) * 2 >= step ) { - alignValue += ( valModStep > 0 ) ? step : ( -step ); - } - - // Since JavaScript has problems with large floats, round - // the final value to 5 digits after the decimal point (see #4124) - return parseFloat( alignValue.toFixed(5) ); - }, - - _valueMin: function() { - return this.options.min; - }, - - _valueMax: function() { - return this.options.max; - }, - - _refreshValue: function() { - var lastValPercent, valPercent, value, valueMin, valueMax, - oRange = this.options.range, - o = this.options, - that = this, - animate = ( !this._animateOff ) ? o.animate : false, - _set = {}; - - if ( this.options.values && this.options.values.length ) { - this.handles.each(function( i ) { - valPercent = ( that.values(i) - that._valueMin() ) / ( that._valueMax() - that._valueMin() ) * 100; - _set[ that.orientation === "horizontal" ? "left" : "bottom" ] = valPercent + "%"; - $( this ).stop( 1, 1 )[ animate ? "animate" : "css" ]( _set, o.animate ); - if ( that.options.range === true ) { - if ( that.orientation === "horizontal" ) { - if ( i === 0 ) { - that.range.stop( 1, 1 )[ animate ? "animate" : "css" ]( { left: valPercent + "%" }, o.animate ); - } - if ( i === 1 ) { - that.range[ animate ? "animate" : "css" ]( { width: ( valPercent - lastValPercent ) + "%" }, { queue: false, duration: o.animate } ); - } - } else { - if ( i === 0 ) { - that.range.stop( 1, 1 )[ animate ? "animate" : "css" ]( { bottom: ( valPercent ) + "%" }, o.animate ); - } - if ( i === 1 ) { - that.range[ animate ? "animate" : "css" ]( { height: ( valPercent - lastValPercent ) + "%" }, { queue: false, duration: o.animate } ); - } - } - } - lastValPercent = valPercent; - }); - } else { - value = this.value(); - valueMin = this._valueMin(); - valueMax = this._valueMax(); - valPercent = ( valueMax !== valueMin ) ? - ( value - valueMin ) / ( valueMax - valueMin ) * 100 : - 0; - _set[ this.orientation === "horizontal" ? "left" : "bottom" ] = valPercent + "%"; - this.handle.stop( 1, 1 )[ animate ? "animate" : "css" ]( _set, o.animate ); - - if ( oRange === "min" && this.orientation === "horizontal" ) { - this.range.stop( 1, 1 )[ animate ? "animate" : "css" ]( { width: valPercent + "%" }, o.animate ); - } - if ( oRange === "max" && this.orientation === "horizontal" ) { - this.range[ animate ? "animate" : "css" ]( { width: ( 100 - valPercent ) + "%" }, { queue: false, duration: o.animate } ); - } - if ( oRange === "min" && this.orientation === "vertical" ) { - this.range.stop( 1, 1 )[ animate ? "animate" : "css" ]( { height: valPercent + "%" }, o.animate ); - } - if ( oRange === "max" && this.orientation === "vertical" ) { - this.range[ animate ? "animate" : "css" ]( { height: ( 100 - valPercent ) + "%" }, { queue: false, duration: o.animate } ); - } - } - } - -}); - -}(jQuery)); - -(function( $ ) { - -function modifier( fn ) { - return function() { - var previous = this.element.val(); - fn.apply( this, arguments ); - this._refresh(); - if ( previous !== this.element.val() ) { - this._trigger( "change" ); - } - }; -} - -$.widget( "ui.spinner", { - version: "1.9.2", - defaultElement: "", - widgetEventPrefix: "spin", - options: { - culture: null, - icons: { - down: "ui-icon-triangle-1-s", - up: "ui-icon-triangle-1-n" - }, - incremental: true, - max: null, - min: null, - numberFormat: null, - page: 10, - step: 1, - - change: null, - spin: null, - start: null, - stop: null - }, - - _create: function() { - // handle string values that need to be parsed - this._setOption( "max", this.options.max ); - this._setOption( "min", this.options.min ); - this._setOption( "step", this.options.step ); - - // format the value, but don't constrain - this._value( this.element.val(), true ); - - this._draw(); - this._on( this._events ); - this._refresh(); - - // turning off autocomplete prevents the browser from remembering the - // value when navigating through history, so we re-enable autocomplete - // if the page is unloaded before the widget is destroyed. #7790 - this._on( this.window, { - beforeunload: function() { - this.element.removeAttr( "autocomplete" ); - } - }); - }, - - _getCreateOptions: function() { - var options = {}, - element = this.element; - - $.each( [ "min", "max", "step" ], function( i, option ) { - var value = element.attr( option ); - if ( value !== undefined && value.length ) { - options[ option ] = value; - } - }); - - return options; - }, - - _events: { - keydown: function( event ) { - if ( this._start( event ) && this._keydown( event ) ) { - event.preventDefault(); - } - }, - keyup: "_stop", - focus: function() { - this.previous = this.element.val(); - }, - blur: function( event ) { - if ( this.cancelBlur ) { - delete this.cancelBlur; - return; - } - - this._refresh(); - if ( this.previous !== this.element.val() ) { - this._trigger( "change", event ); - } - }, - mousewheel: function( event, delta ) { - if ( !delta ) { - return; - } - if ( !this.spinning && !this._start( event ) ) { - return false; - } - - this._spin( (delta > 0 ? 1 : -1) * this.options.step, event ); - clearTimeout( this.mousewheelTimer ); - this.mousewheelTimer = this._delay(function() { - if ( this.spinning ) { - this._stop( event ); - } - }, 100 ); - event.preventDefault(); - }, - "mousedown .ui-spinner-button": function( event ) { - var previous; - - // We never want the buttons to have focus; whenever the user is - // interacting with the spinner, the focus should be on the input. - // If the input is focused then this.previous is properly set from - // when the input first received focus. If the input is not focused - // then we need to set this.previous based on the value before spinning. - previous = this.element[0] === this.document[0].activeElement ? - this.previous : this.element.val(); - function checkFocus() { - var isActive = this.element[0] === this.document[0].activeElement; - if ( !isActive ) { - this.element.focus(); - this.previous = previous; - // support: IE - // IE sets focus asynchronously, so we need to check if focus - // moved off of the input because the user clicked on the button. - this._delay(function() { - this.previous = previous; - }); - } - } - - // ensure focus is on (or stays on) the text field - event.preventDefault(); - checkFocus.call( this ); - - // support: IE - // IE doesn't prevent moving focus even with event.preventDefault() - // so we set a flag to know when we should ignore the blur event - // and check (again) if focus moved off of the input. - this.cancelBlur = true; - this._delay(function() { - delete this.cancelBlur; - checkFocus.call( this ); - }); - - if ( this._start( event ) === false ) { - return; - } - - this._repeat( null, $( event.currentTarget ).hasClass( "ui-spinner-up" ) ? 1 : -1, event ); - }, - "mouseup .ui-spinner-button": "_stop", - "mouseenter .ui-spinner-button": function( event ) { - // button will add ui-state-active if mouse was down while mouseleave and kept down - if ( !$( event.currentTarget ).hasClass( "ui-state-active" ) ) { - return; - } - - if ( this._start( event ) === false ) { - return false; - } - this._repeat( null, $( event.currentTarget ).hasClass( "ui-spinner-up" ) ? 1 : -1, event ); - }, - // TODO: do we really want to consider this a stop? - // shouldn't we just stop the repeater and wait until mouseup before - // we trigger the stop event? - "mouseleave .ui-spinner-button": "_stop" - }, - - _draw: function() { - var uiSpinner = this.uiSpinner = this.element - .addClass( "ui-spinner-input" ) - .attr( "autocomplete", "off" ) - .wrap( this._uiSpinnerHtml() ) - .parent() - // add buttons - .append( this._buttonHtml() ); - - this.element.attr( "role", "spinbutton" ); - - // button bindings - this.buttons = uiSpinner.find( ".ui-spinner-button" ) - .attr( "tabIndex", -1 ) - .button() - .removeClass( "ui-corner-all" ); - - // IE 6 doesn't understand height: 50% for the buttons - // unless the wrapper has an explicit height - if ( this.buttons.height() > Math.ceil( uiSpinner.height() * 0.5 ) && - uiSpinner.height() > 0 ) { - uiSpinner.height( uiSpinner.height() ); - } - - // disable spinner if element was already disabled - if ( this.options.disabled ) { - this.disable(); - } - }, - - _keydown: function( event ) { - var options = this.options, - keyCode = $.ui.keyCode; - - switch ( event.keyCode ) { - case keyCode.UP: - this._repeat( null, 1, event ); - return true; - case keyCode.DOWN: - this._repeat( null, -1, event ); - return true; - case keyCode.PAGE_UP: - this._repeat( null, options.page, event ); - return true; - case keyCode.PAGE_DOWN: - this._repeat( null, -options.page, event ); - return true; - } - - return false; - }, - - _uiSpinnerHtml: function() { - return ""; - }, - - _buttonHtml: function() { - return "" + - "" + - "" + - "" + - "" + - "" + - ""; - }, - - _start: function( event ) { - if ( !this.spinning && this._trigger( "start", event ) === false ) { - return false; - } - - if ( !this.counter ) { - this.counter = 1; - } - this.spinning = true; - return true; - }, - - _repeat: function( i, steps, event ) { - i = i || 500; - - clearTimeout( this.timer ); - this.timer = this._delay(function() { - this._repeat( 40, steps, event ); - }, i ); - - this._spin( steps * this.options.step, event ); - }, - - _spin: function( step, event ) { - var value = this.value() || 0; - - if ( !this.counter ) { - this.counter = 1; - } - - value = this._adjustValue( value + step * this._increment( this.counter ) ); - - if ( !this.spinning || this._trigger( "spin", event, { value: value } ) !== false) { - this._value( value ); - this.counter++; - } - }, - - _increment: function( i ) { - var incremental = this.options.incremental; - - if ( incremental ) { - return $.isFunction( incremental ) ? - incremental( i ) : - Math.floor( i*i*i/50000 - i*i/500 + 17*i/200 + 1 ); - } - - return 1; - }, - - _precision: function() { - var precision = this._precisionOf( this.options.step ); - if ( this.options.min !== null ) { - precision = Math.max( precision, this._precisionOf( this.options.min ) ); - } - return precision; - }, - - _precisionOf: function( num ) { - var str = num.toString(), - decimal = str.indexOf( "." ); - return decimal === -1 ? 0 : str.length - decimal - 1; - }, - - _adjustValue: function( value ) { - var base, aboveMin, - options = this.options; - - // make sure we're at a valid step - // - find out where we are relative to the base (min or 0) - base = options.min !== null ? options.min : 0; - aboveMin = value - base; - // - round to the nearest step - aboveMin = Math.round(aboveMin / options.step) * options.step; - // - rounding is based on 0, so adjust back to our base - value = base + aboveMin; - - // fix precision from bad JS floating point math - value = parseFloat( value.toFixed( this._precision() ) ); - - // clamp the value - if ( options.max !== null && value > options.max) { - return options.max; - } - if ( options.min !== null && value < options.min ) { - return options.min; - } - - return value; - }, - - _stop: function( event ) { - if ( !this.spinning ) { - return; - } - - clearTimeout( this.timer ); - clearTimeout( this.mousewheelTimer ); - this.counter = 0; - this.spinning = false; - this._trigger( "stop", event ); - }, - - _setOption: function( key, value ) { - if ( key === "culture" || key === "numberFormat" ) { - var prevValue = this._parse( this.element.val() ); - this.options[ key ] = value; - this.element.val( this._format( prevValue ) ); - return; - } - - if ( key === "max" || key === "min" || key === "step" ) { - if ( typeof value === "string" ) { - value = this._parse( value ); - } - } - - this._super( key, value ); - - if ( key === "disabled" ) { - if ( value ) { - this.element.prop( "disabled", true ); - this.buttons.button( "disable" ); - } else { - this.element.prop( "disabled", false ); - this.buttons.button( "enable" ); - } - } - }, - - _setOptions: modifier(function( options ) { - this._super( options ); - this._value( this.element.val() ); - }), - - _parse: function( val ) { - if ( typeof val === "string" && val !== "" ) { - val = window.Globalize && this.options.numberFormat ? - Globalize.parseFloat( val, 10, this.options.culture ) : +val; - } - return val === "" || isNaN( val ) ? null : val; - }, - - _format: function( value ) { - if ( value === "" ) { - return ""; - } - return window.Globalize && this.options.numberFormat ? - Globalize.format( value, this.options.numberFormat, this.options.culture ) : - value; - }, - - _refresh: function() { - this.element.attr({ - "aria-valuemin": this.options.min, - "aria-valuemax": this.options.max, - // TODO: what should we do with values that can't be parsed? - "aria-valuenow": this._parse( this.element.val() ) - }); - }, - - // update the value without triggering change - _value: function( value, allowAny ) { - var parsed; - if ( value !== "" ) { - parsed = this._parse( value ); - if ( parsed !== null ) { - if ( !allowAny ) { - parsed = this._adjustValue( parsed ); - } - value = this._format( parsed ); - } - } - this.element.val( value ); - this._refresh(); - }, - - _destroy: function() { - this.element - .removeClass( "ui-spinner-input" ) - .prop( "disabled", false ) - .removeAttr( "autocomplete" ) - .removeAttr( "role" ) - .removeAttr( "aria-valuemin" ) - .removeAttr( "aria-valuemax" ) - .removeAttr( "aria-valuenow" ); - this.uiSpinner.replaceWith( this.element ); - }, - - stepUp: modifier(function( steps ) { - this._stepUp( steps ); - }), - _stepUp: function( steps ) { - this._spin( (steps || 1) * this.options.step ); - }, - - stepDown: modifier(function( steps ) { - this._stepDown( steps ); - }), - _stepDown: function( steps ) { - this._spin( (steps || 1) * -this.options.step ); - }, - - pageUp: modifier(function( pages ) { - this._stepUp( (pages || 1) * this.options.page ); - }), - - pageDown: modifier(function( pages ) { - this._stepDown( (pages || 1) * this.options.page ); - }), - - value: function( newVal ) { - if ( !arguments.length ) { - return this._parse( this.element.val() ); - } - modifier( this._value ).call( this, newVal ); - }, - - widget: function() { - return this.uiSpinner; - } -}); - -}( jQuery ) ); - -(function( $, undefined ) { - -var tabId = 0, - rhash = /#.*$/; - -function getNextTabId() { - return ++tabId; -} - -function isLocal( anchor ) { - return anchor.hash.length > 1 && - anchor.href.replace( rhash, "" ) === - location.href.replace( rhash, "" ) - // support: Safari 5.1 - // Safari 5.1 doesn't encode spaces in window.location - // but it does encode spaces from anchors (#8777) - .replace( /\s/g, "%20" ); -} - -$.widget( "ui.tabs", { - version: "1.9.2", - delay: 300, - options: { - active: null, - collapsible: false, - event: "click", - heightStyle: "content", - hide: null, - show: null, - - // callbacks - activate: null, - beforeActivate: null, - beforeLoad: null, - load: null - }, - - _create: function() { - var that = this, - options = this.options, - active = options.active, - locationHash = location.hash.substring( 1 ); - - this.running = false; - - this.element - .addClass( "ui-tabs ui-widget ui-widget-content ui-corner-all" ) - .toggleClass( "ui-tabs-collapsible", options.collapsible ) - // Prevent users from focusing disabled tabs via click - .delegate( ".ui-tabs-nav > li", "mousedown" + this.eventNamespace, function( event ) { - if ( $( this ).is( ".ui-state-disabled" ) ) { - event.preventDefault(); - } - }) - // support: IE <9 - // Preventing the default action in mousedown doesn't prevent IE - // from focusing the element, so if the anchor gets focused, blur. - // We don't have to worry about focusing the previously focused - // element since clicking on a non-focusable element should focus - // the body anyway. - .delegate( ".ui-tabs-anchor", "focus" + this.eventNamespace, function() { - if ( $( this ).closest( "li" ).is( ".ui-state-disabled" ) ) { - this.blur(); - } - }); - - this._processTabs(); - - if ( active === null ) { - // check the fragment identifier in the URL - if ( locationHash ) { - this.tabs.each(function( i, tab ) { - if ( $( tab ).attr( "aria-controls" ) === locationHash ) { - active = i; - return false; - } - }); - } - - // check for a tab marked active via a class - if ( active === null ) { - active = this.tabs.index( this.tabs.filter( ".ui-tabs-active" ) ); - } - - // no active tab, set to false - if ( active === null || active === -1 ) { - active = this.tabs.length ? 0 : false; - } - } - - // handle numbers: negative, out of range - if ( active !== false ) { - active = this.tabs.index( this.tabs.eq( active ) ); - if ( active === -1 ) { - active = options.collapsible ? false : 0; - } - } - options.active = active; - - // don't allow collapsible: false and active: false - if ( !options.collapsible && options.active === false && this.anchors.length ) { - options.active = 0; - } - - // Take disabling tabs via class attribute from HTML - // into account and update option properly. - if ( $.isArray( options.disabled ) ) { - options.disabled = $.unique( options.disabled.concat( - $.map( this.tabs.filter( ".ui-state-disabled" ), function( li ) { - return that.tabs.index( li ); - }) - ) ).sort(); - } - - // check for length avoids error when initializing empty list - if ( this.options.active !== false && this.anchors.length ) { - this.active = this._findActive( this.options.active ); - } else { - this.active = $(); - } - - this._refresh(); - - if ( this.active.length ) { - this.load( options.active ); - } - }, - - _getCreateEventData: function() { - return { - tab: this.active, - panel: !this.active.length ? $() : this._getPanelForTab( this.active ) - }; - }, - - _tabKeydown: function( event ) { - var focusedTab = $( this.document[0].activeElement ).closest( "li" ), - selectedIndex = this.tabs.index( focusedTab ), - goingForward = true; - - if ( this._handlePageNav( event ) ) { - return; - } - - switch ( event.keyCode ) { - case $.ui.keyCode.RIGHT: - case $.ui.keyCode.DOWN: - selectedIndex++; - break; - case $.ui.keyCode.UP: - case $.ui.keyCode.LEFT: - goingForward = false; - selectedIndex--; - break; - case $.ui.keyCode.END: - selectedIndex = this.anchors.length - 1; - break; - case $.ui.keyCode.HOME: - selectedIndex = 0; - break; - case $.ui.keyCode.SPACE: - // Activate only, no collapsing - event.preventDefault(); - clearTimeout( this.activating ); - this._activate( selectedIndex ); - return; - case $.ui.keyCode.ENTER: - // Toggle (cancel delayed activation, allow collapsing) - event.preventDefault(); - clearTimeout( this.activating ); - // Determine if we should collapse or activate - this._activate( selectedIndex === this.options.active ? false : selectedIndex ); - return; - default: - return; - } - - // Focus the appropriate tab, based on which key was pressed - event.preventDefault(); - clearTimeout( this.activating ); - selectedIndex = this._focusNextTab( selectedIndex, goingForward ); - - // Navigating with control key will prevent automatic activation - if ( !event.ctrlKey ) { - // Update aria-selected immediately so that AT think the tab is already selected. - // Otherwise AT may confuse the user by stating that they need to activate the tab, - // but the tab will already be activated by the time the announcement finishes. - focusedTab.attr( "aria-selected", "false" ); - this.tabs.eq( selectedIndex ).attr( "aria-selected", "true" ); - - this.activating = this._delay(function() { - this.option( "active", selectedIndex ); - }, this.delay ); - } - }, - - _panelKeydown: function( event ) { - if ( this._handlePageNav( event ) ) { - return; - } - - // Ctrl+up moves focus to the current tab - if ( event.ctrlKey && event.keyCode === $.ui.keyCode.UP ) { - event.preventDefault(); - this.active.focus(); - } - }, - - // Alt+page up/down moves focus to the previous/next tab (and activates) - _handlePageNav: function( event ) { - if ( event.altKey && event.keyCode === $.ui.keyCode.PAGE_UP ) { - this._activate( this._focusNextTab( this.options.active - 1, false ) ); - return true; - } - if ( event.altKey && event.keyCode === $.ui.keyCode.PAGE_DOWN ) { - this._activate( this._focusNextTab( this.options.active + 1, true ) ); - return true; - } - }, - - _findNextTab: function( index, goingForward ) { - var lastTabIndex = this.tabs.length - 1; - - function constrain() { - if ( index > lastTabIndex ) { - index = 0; - } - if ( index < 0 ) { - index = lastTabIndex; - } - return index; - } - - while ( $.inArray( constrain(), this.options.disabled ) !== -1 ) { - index = goingForward ? index + 1 : index - 1; - } - - return index; - }, - - _focusNextTab: function( index, goingForward ) { - index = this._findNextTab( index, goingForward ); - this.tabs.eq( index ).focus(); - return index; - }, - - _setOption: function( key, value ) { - if ( key === "active" ) { - // _activate() will handle invalid values and update this.options - this._activate( value ); - return; - } - - if ( key === "disabled" ) { - // don't use the widget factory's disabled handling - this._setupDisabled( value ); - return; - } - - this._super( key, value); - - if ( key === "collapsible" ) { - this.element.toggleClass( "ui-tabs-collapsible", value ); - // Setting collapsible: false while collapsed; open first panel - if ( !value && this.options.active === false ) { - this._activate( 0 ); - } - } - - if ( key === "event" ) { - this._setupEvents( value ); - } - - if ( key === "heightStyle" ) { - this._setupHeightStyle( value ); - } - }, - - _tabId: function( tab ) { - return tab.attr( "aria-controls" ) || "ui-tabs-" + getNextTabId(); - }, - - _sanitizeSelector: function( hash ) { - return hash ? hash.replace( /[!"$%&'()*+,.\/:;<=>?@\[\]\^`{|}~]/g, "\\$&" ) : ""; - }, - - refresh: function() { - var options = this.options, - lis = this.tablist.children( ":has(a[href])" ); - - // get disabled tabs from class attribute from HTML - // this will get converted to a boolean if needed in _refresh() - options.disabled = $.map( lis.filter( ".ui-state-disabled" ), function( tab ) { - return lis.index( tab ); - }); - - this._processTabs(); - - // was collapsed or no tabs - if ( options.active === false || !this.anchors.length ) { - options.active = false; - this.active = $(); - // was active, but active tab is gone - } else if ( this.active.length && !$.contains( this.tablist[ 0 ], this.active[ 0 ] ) ) { - // all remaining tabs are disabled - if ( this.tabs.length === options.disabled.length ) { - options.active = false; - this.active = $(); - // activate previous tab - } else { - this._activate( this._findNextTab( Math.max( 0, options.active - 1 ), false ) ); - } - // was active, active tab still exists - } else { - // make sure active index is correct - options.active = this.tabs.index( this.active ); - } - - this._refresh(); - }, - - _refresh: function() { - this._setupDisabled( this.options.disabled ); - this._setupEvents( this.options.event ); - this._setupHeightStyle( this.options.heightStyle ); - - this.tabs.not( this.active ).attr({ - "aria-selected": "false", - tabIndex: -1 - }); - this.panels.not( this._getPanelForTab( this.active ) ) - .hide() - .attr({ - "aria-expanded": "false", - "aria-hidden": "true" - }); - - // Make sure one tab is in the tab order - if ( !this.active.length ) { - this.tabs.eq( 0 ).attr( "tabIndex", 0 ); - } else { - this.active - .addClass( "ui-tabs-active ui-state-active" ) - .attr({ - "aria-selected": "true", - tabIndex: 0 - }); - this._getPanelForTab( this.active ) - .show() - .attr({ - "aria-expanded": "true", - "aria-hidden": "false" - }); - } - }, - - _processTabs: function() { - var that = this; - - this.tablist = this._getList() - .addClass( "ui-tabs-nav ui-helper-reset ui-helper-clearfix ui-widget-header ui-corner-all" ) - .attr( "role", "tablist" ); - - this.tabs = this.tablist.find( "> li:has(a[href])" ) - .addClass( "ui-state-default ui-corner-top" ) - .attr({ - role: "tab", - tabIndex: -1 - }); - - this.anchors = this.tabs.map(function() { - return $( "a", this )[ 0 ]; - }) - .addClass( "ui-tabs-anchor" ) - .attr({ - role: "presentation", - tabIndex: -1 - }); - - this.panels = $(); - - this.anchors.each(function( i, anchor ) { - var selector, panel, panelId, - anchorId = $( anchor ).uniqueId().attr( "id" ), - tab = $( anchor ).closest( "li" ), - originalAriaControls = tab.attr( "aria-controls" ); - - // inline tab - if ( isLocal( anchor ) ) { - selector = anchor.hash; - panel = that.element.find( that._sanitizeSelector( selector ) ); - // remote tab - } else { - panelId = that._tabId( tab ); - selector = "#" + panelId; - panel = that.element.find( selector ); - if ( !panel.length ) { - panel = that._createPanel( panelId ); - panel.insertAfter( that.panels[ i - 1 ] || that.tablist ); - } - panel.attr( "aria-live", "polite" ); - } - - if ( panel.length) { - that.panels = that.panels.add( panel ); - } - if ( originalAriaControls ) { - tab.data( "ui-tabs-aria-controls", originalAriaControls ); - } - tab.attr({ - "aria-controls": selector.substring( 1 ), - "aria-labelledby": anchorId - }); - panel.attr( "aria-labelledby", anchorId ); - }); - - this.panels - .addClass( "ui-tabs-panel ui-widget-content ui-corner-bottom" ) - .attr( "role", "tabpanel" ); - }, - - // allow overriding how to find the list for rare usage scenarios (#7715) - _getList: function() { - return this.element.find( "ol,ul" ).eq( 0 ); - }, - - _createPanel: function( id ) { - return $( "
    " ) - .attr( "id", id ) - .addClass( "ui-tabs-panel ui-widget-content ui-corner-bottom" ) - .data( "ui-tabs-destroy", true ); - }, - - _setupDisabled: function( disabled ) { - if ( $.isArray( disabled ) ) { - if ( !disabled.length ) { - disabled = false; - } else if ( disabled.length === this.anchors.length ) { - disabled = true; - } - } - - // disable tabs - for ( var i = 0, li; ( li = this.tabs[ i ] ); i++ ) { - if ( disabled === true || $.inArray( i, disabled ) !== -1 ) { - $( li ) - .addClass( "ui-state-disabled" ) - .attr( "aria-disabled", "true" ); - } else { - $( li ) - .removeClass( "ui-state-disabled" ) - .removeAttr( "aria-disabled" ); - } - } - - this.options.disabled = disabled; - }, - - _setupEvents: function( event ) { - var events = { - click: function( event ) { - event.preventDefault(); - } - }; - if ( event ) { - $.each( event.split(" "), function( index, eventName ) { - events[ eventName ] = "_eventHandler"; - }); - } - - this._off( this.anchors.add( this.tabs ).add( this.panels ) ); - this._on( this.anchors, events ); - this._on( this.tabs, { keydown: "_tabKeydown" } ); - this._on( this.panels, { keydown: "_panelKeydown" } ); - - this._focusable( this.tabs ); - this._hoverable( this.tabs ); - }, - - _setupHeightStyle: function( heightStyle ) { - var maxHeight, overflow, - parent = this.element.parent(); - - if ( heightStyle === "fill" ) { - // IE 6 treats height like minHeight, so we need to turn off overflow - // in order to get a reliable height - // we use the minHeight support test because we assume that only - // browsers that don't support minHeight will treat height as minHeight - if ( !$.support.minHeight ) { - overflow = parent.css( "overflow" ); - parent.css( "overflow", "hidden"); - } - maxHeight = parent.height(); - this.element.siblings( ":visible" ).each(function() { - var elem = $( this ), - position = elem.css( "position" ); - - if ( position === "absolute" || position === "fixed" ) { - return; - } - maxHeight -= elem.outerHeight( true ); - }); - if ( overflow ) { - parent.css( "overflow", overflow ); - } - - this.element.children().not( this.panels ).each(function() { - maxHeight -= $( this ).outerHeight( true ); - }); - - this.panels.each(function() { - $( this ).height( Math.max( 0, maxHeight - - $( this ).innerHeight() + $( this ).height() ) ); - }) - .css( "overflow", "auto" ); - } else if ( heightStyle === "auto" ) { - maxHeight = 0; - this.panels.each(function() { - maxHeight = Math.max( maxHeight, $( this ).height( "" ).height() ); - }).height( maxHeight ); - } - }, - - _eventHandler: function( event ) { - var options = this.options, - active = this.active, - anchor = $( event.currentTarget ), - tab = anchor.closest( "li" ), - clickedIsActive = tab[ 0 ] === active[ 0 ], - collapsing = clickedIsActive && options.collapsible, - toShow = collapsing ? $() : this._getPanelForTab( tab ), - toHide = !active.length ? $() : this._getPanelForTab( active ), - eventData = { - oldTab: active, - oldPanel: toHide, - newTab: collapsing ? $() : tab, - newPanel: toShow - }; - - event.preventDefault(); - - if ( tab.hasClass( "ui-state-disabled" ) || - // tab is already loading - tab.hasClass( "ui-tabs-loading" ) || - // can't switch durning an animation - this.running || - // click on active header, but not collapsible - ( clickedIsActive && !options.collapsible ) || - // allow canceling activation - ( this._trigger( "beforeActivate", event, eventData ) === false ) ) { - return; - } - - options.active = collapsing ? false : this.tabs.index( tab ); - - this.active = clickedIsActive ? $() : tab; - if ( this.xhr ) { - this.xhr.abort(); - } - - if ( !toHide.length && !toShow.length ) { - $.error( "jQuery UI Tabs: Mismatching fragment identifier." ); - } - - if ( toShow.length ) { - this.load( this.tabs.index( tab ), event ); - } - this._toggle( event, eventData ); - }, - - // handles show/hide for selecting tabs - _toggle: function( event, eventData ) { - var that = this, - toShow = eventData.newPanel, - toHide = eventData.oldPanel; - - this.running = true; - - function complete() { - that.running = false; - that._trigger( "activate", event, eventData ); - } - - function show() { - eventData.newTab.closest( "li" ).addClass( "ui-tabs-active ui-state-active" ); - - if ( toShow.length && that.options.show ) { - that._show( toShow, that.options.show, complete ); - } else { - toShow.show(); - complete(); - } - } - - // start out by hiding, then showing, then completing - if ( toHide.length && this.options.hide ) { - this._hide( toHide, this.options.hide, function() { - eventData.oldTab.closest( "li" ).removeClass( "ui-tabs-active ui-state-active" ); - show(); - }); - } else { - eventData.oldTab.closest( "li" ).removeClass( "ui-tabs-active ui-state-active" ); - toHide.hide(); - show(); - } - - toHide.attr({ - "aria-expanded": "false", - "aria-hidden": "true" - }); - eventData.oldTab.attr( "aria-selected", "false" ); - // If we're switching tabs, remove the old tab from the tab order. - // If we're opening from collapsed state, remove the previous tab from the tab order. - // If we're collapsing, then keep the collapsing tab in the tab order. - if ( toShow.length && toHide.length ) { - eventData.oldTab.attr( "tabIndex", -1 ); - } else if ( toShow.length ) { - this.tabs.filter(function() { - return $( this ).attr( "tabIndex" ) === 0; - }) - .attr( "tabIndex", -1 ); - } - - toShow.attr({ - "aria-expanded": "true", - "aria-hidden": "false" - }); - eventData.newTab.attr({ - "aria-selected": "true", - tabIndex: 0 - }); - }, - - _activate: function( index ) { - var anchor, - active = this._findActive( index ); - - // trying to activate the already active panel - if ( active[ 0 ] === this.active[ 0 ] ) { - return; - } - - // trying to collapse, simulate a click on the current active header - if ( !active.length ) { - active = this.active; - } - - anchor = active.find( ".ui-tabs-anchor" )[ 0 ]; - this._eventHandler({ - target: anchor, - currentTarget: anchor, - preventDefault: $.noop - }); - }, - - _findActive: function( index ) { - return index === false ? $() : this.tabs.eq( index ); - }, - - _getIndex: function( index ) { - // meta-function to give users option to provide a href string instead of a numerical index. - if ( typeof index === "string" ) { - index = this.anchors.index( this.anchors.filter( "[href$='" + index + "']" ) ); - } - - return index; - }, - - _destroy: function() { - if ( this.xhr ) { - this.xhr.abort(); - } - - this.element.removeClass( "ui-tabs ui-widget ui-widget-content ui-corner-all ui-tabs-collapsible" ); - - this.tablist - .removeClass( "ui-tabs-nav ui-helper-reset ui-helper-clearfix ui-widget-header ui-corner-all" ) - .removeAttr( "role" ); - - this.anchors - .removeClass( "ui-tabs-anchor" ) - .removeAttr( "role" ) - .removeAttr( "tabIndex" ) - .removeData( "href.tabs" ) - .removeData( "load.tabs" ) - .removeUniqueId(); - - this.tabs.add( this.panels ).each(function() { - if ( $.data( this, "ui-tabs-destroy" ) ) { - $( this ).remove(); - } else { - $( this ) - .removeClass( "ui-state-default ui-state-active ui-state-disabled " + - "ui-corner-top ui-corner-bottom ui-widget-content ui-tabs-active ui-tabs-panel" ) - .removeAttr( "tabIndex" ) - .removeAttr( "aria-live" ) - .removeAttr( "aria-busy" ) - .removeAttr( "aria-selected" ) - .removeAttr( "aria-labelledby" ) - .removeAttr( "aria-hidden" ) - .removeAttr( "aria-expanded" ) - .removeAttr( "role" ); - } - }); - - this.tabs.each(function() { - var li = $( this ), - prev = li.data( "ui-tabs-aria-controls" ); - if ( prev ) { - li.attr( "aria-controls", prev ); - } else { - li.removeAttr( "aria-controls" ); - } - }); - - this.panels.show(); - - if ( this.options.heightStyle !== "content" ) { - this.panels.css( "height", "" ); - } - }, - - enable: function( index ) { - var disabled = this.options.disabled; - if ( disabled === false ) { - return; - } - - if ( index === undefined ) { - disabled = false; - } else { - index = this._getIndex( index ); - if ( $.isArray( disabled ) ) { - disabled = $.map( disabled, function( num ) { - return num !== index ? num : null; - }); - } else { - disabled = $.map( this.tabs, function( li, num ) { - return num !== index ? num : null; - }); - } - } - this._setupDisabled( disabled ); - }, - - disable: function( index ) { - var disabled = this.options.disabled; - if ( disabled === true ) { - return; - } - - if ( index === undefined ) { - disabled = true; - } else { - index = this._getIndex( index ); - if ( $.inArray( index, disabled ) !== -1 ) { - return; - } - if ( $.isArray( disabled ) ) { - disabled = $.merge( [ index ], disabled ).sort(); - } else { - disabled = [ index ]; - } - } - this._setupDisabled( disabled ); - }, - - load: function( index, event ) { - index = this._getIndex( index ); - var that = this, - tab = this.tabs.eq( index ), - anchor = tab.find( ".ui-tabs-anchor" ), - panel = this._getPanelForTab( tab ), - eventData = { - tab: tab, - panel: panel - }; - - // not remote - if ( isLocal( anchor[ 0 ] ) ) { - return; - } - - this.xhr = $.ajax( this._ajaxSettings( anchor, event, eventData ) ); - - // support: jQuery <1.8 - // jQuery <1.8 returns false if the request is canceled in beforeSend, - // but as of 1.8, $.ajax() always returns a jqXHR object. - if ( this.xhr && this.xhr.statusText !== "canceled" ) { - tab.addClass( "ui-tabs-loading" ); - panel.attr( "aria-busy", "true" ); - - this.xhr - .success(function( response ) { - // support: jQuery <1.8 - // http://bugs.jquery.com/ticket/11778 - setTimeout(function() { - panel.html( response ); - that._trigger( "load", event, eventData ); - }, 1 ); - }) - .complete(function( jqXHR, status ) { - // support: jQuery <1.8 - // http://bugs.jquery.com/ticket/11778 - setTimeout(function() { - if ( status === "abort" ) { - that.panels.stop( false, true ); - } - - tab.removeClass( "ui-tabs-loading" ); - panel.removeAttr( "aria-busy" ); - - if ( jqXHR === that.xhr ) { - delete that.xhr; - } - }, 1 ); - }); - } - }, - - // TODO: Remove this function in 1.10 when ajaxOptions is removed - _ajaxSettings: function( anchor, event, eventData ) { - var that = this; - return { - url: anchor.attr( "href" ), - beforeSend: function( jqXHR, settings ) { - return that._trigger( "beforeLoad", event, - $.extend( { jqXHR : jqXHR, ajaxSettings: settings }, eventData ) ); - } - }; - }, - - _getPanelForTab: function( tab ) { - var id = $( tab ).attr( "aria-controls" ); - return this.element.find( this._sanitizeSelector( "#" + id ) ); - } -}); - -// DEPRECATED -if ( $.uiBackCompat !== false ) { - - // helper method for a lot of the back compat extensions - $.ui.tabs.prototype._ui = function( tab, panel ) { - return { - tab: tab, - panel: panel, - index: this.anchors.index( tab ) - }; - }; - - // url method - $.widget( "ui.tabs", $.ui.tabs, { - url: function( index, url ) { - this.anchors.eq( index ).attr( "href", url ); - } - }); - - // TODO: Remove _ajaxSettings() method when removing this extension - // ajaxOptions and cache options - $.widget( "ui.tabs", $.ui.tabs, { - options: { - ajaxOptions: null, - cache: false - }, - - _create: function() { - this._super(); - - var that = this; - - this._on({ tabsbeforeload: function( event, ui ) { - // tab is already cached - if ( $.data( ui.tab[ 0 ], "cache.tabs" ) ) { - event.preventDefault(); - return; - } - - ui.jqXHR.success(function() { - if ( that.options.cache ) { - $.data( ui.tab[ 0 ], "cache.tabs", true ); - } - }); - }}); - }, - - _ajaxSettings: function( anchor, event, ui ) { - var ajaxOptions = this.options.ajaxOptions; - return $.extend( {}, ajaxOptions, { - error: function( xhr, status ) { - try { - // Passing index avoid a race condition when this method is - // called after the user has selected another tab. - // Pass the anchor that initiated this request allows - // loadError to manipulate the tab content panel via $(a.hash) - ajaxOptions.error( - xhr, status, ui.tab.closest( "li" ).index(), ui.tab[ 0 ] ); - } - catch ( error ) {} - } - }, this._superApply( arguments ) ); - }, - - _setOption: function( key, value ) { - // reset cache if switching from cached to not cached - if ( key === "cache" && value === false ) { - this.anchors.removeData( "cache.tabs" ); - } - this._super( key, value ); - }, - - _destroy: function() { - this.anchors.removeData( "cache.tabs" ); - this._super(); - }, - - url: function( index ){ - this.anchors.eq( index ).removeData( "cache.tabs" ); - this._superApply( arguments ); - } - }); - - // abort method - $.widget( "ui.tabs", $.ui.tabs, { - abort: function() { - if ( this.xhr ) { - this.xhr.abort(); - } - } - }); - - // spinner - $.widget( "ui.tabs", $.ui.tabs, { - options: { - spinner: "Loading…" - }, - _create: function() { - this._super(); - this._on({ - tabsbeforeload: function( event, ui ) { - // Don't react to nested tabs or tabs that don't use a spinner - if ( event.target !== this.element[ 0 ] || - !this.options.spinner ) { - return; - } - - var span = ui.tab.find( "span" ), - html = span.html(); - span.html( this.options.spinner ); - ui.jqXHR.complete(function() { - span.html( html ); - }); - } - }); - } - }); - - // enable/disable events - $.widget( "ui.tabs", $.ui.tabs, { - options: { - enable: null, - disable: null - }, - - enable: function( index ) { - var options = this.options, - trigger; - - if ( index && options.disabled === true || - ( $.isArray( options.disabled ) && $.inArray( index, options.disabled ) !== -1 ) ) { - trigger = true; - } - - this._superApply( arguments ); - - if ( trigger ) { - this._trigger( "enable", null, this._ui( this.anchors[ index ], this.panels[ index ] ) ); - } - }, - - disable: function( index ) { - var options = this.options, - trigger; - - if ( index && options.disabled === false || - ( $.isArray( options.disabled ) && $.inArray( index, options.disabled ) === -1 ) ) { - trigger = true; - } - - this._superApply( arguments ); - - if ( trigger ) { - this._trigger( "disable", null, this._ui( this.anchors[ index ], this.panels[ index ] ) ); - } - } - }); - - // add/remove methods and events - $.widget( "ui.tabs", $.ui.tabs, { - options: { - add: null, - remove: null, - tabTemplate: "
  • #{label}
  • " - }, - - add: function( url, label, index ) { - if ( index === undefined ) { - index = this.anchors.length; - } - - var doInsertAfter, panel, - options = this.options, - li = $( options.tabTemplate - .replace( /#\{href\}/g, url ) - .replace( /#\{label\}/g, label ) ), - id = !url.indexOf( "#" ) ? - url.replace( "#", "" ) : - this._tabId( li ); - - li.addClass( "ui-state-default ui-corner-top" ).data( "ui-tabs-destroy", true ); - li.attr( "aria-controls", id ); - - doInsertAfter = index >= this.tabs.length; - - // try to find an existing element before creating a new one - panel = this.element.find( "#" + id ); - if ( !panel.length ) { - panel = this._createPanel( id ); - if ( doInsertAfter ) { - if ( index > 0 ) { - panel.insertAfter( this.panels.eq( -1 ) ); - } else { - panel.appendTo( this.element ); - } - } else { - panel.insertBefore( this.panels[ index ] ); - } - } - panel.addClass( "ui-tabs-panel ui-widget-content ui-corner-bottom" ).hide(); - - if ( doInsertAfter ) { - li.appendTo( this.tablist ); - } else { - li.insertBefore( this.tabs[ index ] ); - } - - options.disabled = $.map( options.disabled, function( n ) { - return n >= index ? ++n : n; - }); - - this.refresh(); - if ( this.tabs.length === 1 && options.active === false ) { - this.option( "active", 0 ); - } - - this._trigger( "add", null, this._ui( this.anchors[ index ], this.panels[ index ] ) ); - return this; - }, - - remove: function( index ) { - index = this._getIndex( index ); - var options = this.options, - tab = this.tabs.eq( index ).remove(), - panel = this._getPanelForTab( tab ).remove(); - - // If selected tab was removed focus tab to the right or - // in case the last tab was removed the tab to the left. - // We check for more than 2 tabs, because if there are only 2, - // then when we remove this tab, there will only be one tab left - // so we don't need to detect which tab to activate. - if ( tab.hasClass( "ui-tabs-active" ) && this.anchors.length > 2 ) { - this._activate( index + ( index + 1 < this.anchors.length ? 1 : -1 ) ); - } - - options.disabled = $.map( - $.grep( options.disabled, function( n ) { - return n !== index; - }), - function( n ) { - return n >= index ? --n : n; - }); - - this.refresh(); - - this._trigger( "remove", null, this._ui( tab.find( "a" )[ 0 ], panel[ 0 ] ) ); - return this; - } - }); - - // length method - $.widget( "ui.tabs", $.ui.tabs, { - length: function() { - return this.anchors.length; - } - }); - - // panel ids (idPrefix option + title attribute) - $.widget( "ui.tabs", $.ui.tabs, { - options: { - idPrefix: "ui-tabs-" - }, - - _tabId: function( tab ) { - var a = tab.is( "li" ) ? tab.find( "a[href]" ) : tab; - a = a[0]; - return $( a ).closest( "li" ).attr( "aria-controls" ) || - a.title && a.title.replace( /\s/g, "_" ).replace( /[^\w\u00c0-\uFFFF\-]/g, "" ) || - this.options.idPrefix + getNextTabId(); - } - }); - - // _createPanel method - $.widget( "ui.tabs", $.ui.tabs, { - options: { - panelTemplate: "
    " - }, - - _createPanel: function( id ) { - return $( this.options.panelTemplate ) - .attr( "id", id ) - .addClass( "ui-tabs-panel ui-widget-content ui-corner-bottom" ) - .data( "ui-tabs-destroy", true ); - } - }); - - // selected option - $.widget( "ui.tabs", $.ui.tabs, { - _create: function() { - var options = this.options; - if ( options.active === null && options.selected !== undefined ) { - options.active = options.selected === -1 ? false : options.selected; - } - this._super(); - options.selected = options.active; - if ( options.selected === false ) { - options.selected = -1; - } - }, - - _setOption: function( key, value ) { - if ( key !== "selected" ) { - return this._super( key, value ); - } - - var options = this.options; - this._super( "active", value === -1 ? false : value ); - options.selected = options.active; - if ( options.selected === false ) { - options.selected = -1; - } - }, - - _eventHandler: function() { - this._superApply( arguments ); - this.options.selected = this.options.active; - if ( this.options.selected === false ) { - this.options.selected = -1; - } - } - }); - - // show and select event - $.widget( "ui.tabs", $.ui.tabs, { - options: { - show: null, - select: null - }, - _create: function() { - this._super(); - if ( this.options.active !== false ) { - this._trigger( "show", null, this._ui( - this.active.find( ".ui-tabs-anchor" )[ 0 ], - this._getPanelForTab( this.active )[ 0 ] ) ); - } - }, - _trigger: function( type, event, data ) { - var tab, panel, - ret = this._superApply( arguments ); - - if ( !ret ) { - return false; - } - - if ( type === "beforeActivate" ) { - tab = data.newTab.length ? data.newTab : data.oldTab; - panel = data.newPanel.length ? data.newPanel : data.oldPanel; - ret = this._super( "select", event, { - tab: tab.find( ".ui-tabs-anchor" )[ 0], - panel: panel[ 0 ], - index: tab.closest( "li" ).index() - }); - } else if ( type === "activate" && data.newTab.length ) { - ret = this._super( "show", event, { - tab: data.newTab.find( ".ui-tabs-anchor" )[ 0 ], - panel: data.newPanel[ 0 ], - index: data.newTab.closest( "li" ).index() - }); - } - return ret; - } - }); - - // select method - $.widget( "ui.tabs", $.ui.tabs, { - select: function( index ) { - index = this._getIndex( index ); - if ( index === -1 ) { - if ( this.options.collapsible && this.options.selected !== -1 ) { - index = this.options.selected; - } else { - return; - } - } - this.anchors.eq( index ).trigger( this.options.event + this.eventNamespace ); - } - }); - - // cookie option - (function() { - - var listId = 0; - - $.widget( "ui.tabs", $.ui.tabs, { - options: { - cookie: null // e.g. { expires: 7, path: '/', domain: 'jquery.com', secure: true } - }, - _create: function() { - var options = this.options, - active; - if ( options.active == null && options.cookie ) { - active = parseInt( this._cookie(), 10 ); - if ( active === -1 ) { - active = false; - } - options.active = active; - } - this._super(); - }, - _cookie: function( active ) { - var cookie = [ this.cookie || - ( this.cookie = this.options.cookie.name || "ui-tabs-" + (++listId) ) ]; - if ( arguments.length ) { - cookie.push( active === false ? -1 : active ); - cookie.push( this.options.cookie ); - } - return $.cookie.apply( null, cookie ); - }, - _refresh: function() { - this._super(); - if ( this.options.cookie ) { - this._cookie( this.options.active, this.options.cookie ); - } - }, - _eventHandler: function() { - this._superApply( arguments ); - if ( this.options.cookie ) { - this._cookie( this.options.active, this.options.cookie ); - } - }, - _destroy: function() { - this._super(); - if ( this.options.cookie ) { - this._cookie( null, this.options.cookie ); - } - } - }); - - })(); - - // load event - $.widget( "ui.tabs", $.ui.tabs, { - _trigger: function( type, event, data ) { - var _data = $.extend( {}, data ); - if ( type === "load" ) { - _data.panel = _data.panel[ 0 ]; - _data.tab = _data.tab.find( ".ui-tabs-anchor" )[ 0 ]; - } - return this._super( type, event, _data ); - } - }); - - // fx option - // The new animation options (show, hide) conflict with the old show callback. - // The old fx option wins over show/hide anyway (always favor back-compat). - // If a user wants to use the new animation API, they must give up the old API. - $.widget( "ui.tabs", $.ui.tabs, { - options: { - fx: null // e.g. { height: "toggle", opacity: "toggle", duration: 200 } - }, - - _getFx: function() { - var hide, show, - fx = this.options.fx; - - if ( fx ) { - if ( $.isArray( fx ) ) { - hide = fx[ 0 ]; - show = fx[ 1 ]; - } else { - hide = show = fx; - } - } - - return fx ? { show: show, hide: hide } : null; - }, - - _toggle: function( event, eventData ) { - var that = this, - toShow = eventData.newPanel, - toHide = eventData.oldPanel, - fx = this._getFx(); - - if ( !fx ) { - return this._super( event, eventData ); - } - - that.running = true; - - function complete() { - that.running = false; - that._trigger( "activate", event, eventData ); - } - - function show() { - eventData.newTab.closest( "li" ).addClass( "ui-tabs-active ui-state-active" ); - - if ( toShow.length && fx.show ) { - toShow - .animate( fx.show, fx.show.duration, function() { - complete(); - }); - } else { - toShow.show(); - complete(); - } - } - - // start out by hiding, then showing, then completing - if ( toHide.length && fx.hide ) { - toHide.animate( fx.hide, fx.hide.duration, function() { - eventData.oldTab.closest( "li" ).removeClass( "ui-tabs-active ui-state-active" ); - show(); - }); - } else { - eventData.oldTab.closest( "li" ).removeClass( "ui-tabs-active ui-state-active" ); - toHide.hide(); - show(); - } - } - }); -} - -})( jQuery ); - -(function( $ ) { - -var increments = 0; - -function addDescribedBy( elem, id ) { - var describedby = (elem.attr( "aria-describedby" ) || "").split( /\s+/ ); - describedby.push( id ); - elem - .data( "ui-tooltip-id", id ) - .attr( "aria-describedby", $.trim( describedby.join( " " ) ) ); -} - -function removeDescribedBy( elem ) { - var id = elem.data( "ui-tooltip-id" ), - describedby = (elem.attr( "aria-describedby" ) || "").split( /\s+/ ), - index = $.inArray( id, describedby ); - if ( index !== -1 ) { - describedby.splice( index, 1 ); - } - - elem.removeData( "ui-tooltip-id" ); - describedby = $.trim( describedby.join( " " ) ); - if ( describedby ) { - elem.attr( "aria-describedby", describedby ); - } else { - elem.removeAttr( "aria-describedby" ); - } -} - -$.widget( "ui.tooltip", { - version: "1.9.2", - options: { - content: function() { - return $( this ).attr( "title" ); - }, - hide: true, - // Disabled elements have inconsistent behavior across browsers (#8661) - items: "[title]:not([disabled])", - position: { - my: "left top+15", - at: "left bottom", - collision: "flipfit flip" - }, - show: true, - tooltipClass: null, - track: false, - - // callbacks - close: null, - open: null - }, - - _create: function() { - this._on({ - mouseover: "open", - focusin: "open" - }); - - // IDs of generated tooltips, needed for destroy - this.tooltips = {}; - // IDs of parent tooltips where we removed the title attribute - this.parents = {}; - - if ( this.options.disabled ) { - this._disable(); - } - }, - - _setOption: function( key, value ) { - var that = this; - - if ( key === "disabled" ) { - this[ value ? "_disable" : "_enable" ](); - this.options[ key ] = value; - // disable element style changes - return; - } - - this._super( key, value ); - - if ( key === "content" ) { - $.each( this.tooltips, function( id, element ) { - that._updateContent( element ); - }); - } - }, - - _disable: function() { - var that = this; - - // close open tooltips - $.each( this.tooltips, function( id, element ) { - var event = $.Event( "blur" ); - event.target = event.currentTarget = element[0]; - that.close( event, true ); - }); - - // remove title attributes to prevent native tooltips - this.element.find( this.options.items ).andSelf().each(function() { - var element = $( this ); - if ( element.is( "[title]" ) ) { - element - .data( "ui-tooltip-title", element.attr( "title" ) ) - .attr( "title", "" ); - } - }); - }, - - _enable: function() { - // restore title attributes - this.element.find( this.options.items ).andSelf().each(function() { - var element = $( this ); - if ( element.data( "ui-tooltip-title" ) ) { - element.attr( "title", element.data( "ui-tooltip-title" ) ); - } - }); - }, - - open: function( event ) { - var that = this, - target = $( event ? event.target : this.element ) - // we need closest here due to mouseover bubbling, - // but always pointing at the same event target - .closest( this.options.items ); - - // No element to show a tooltip for or the tooltip is already open - if ( !target.length || target.data( "ui-tooltip-id" ) ) { - return; - } - - if ( target.attr( "title" ) ) { - target.data( "ui-tooltip-title", target.attr( "title" ) ); - } - - target.data( "ui-tooltip-open", true ); - - // kill parent tooltips, custom or native, for hover - if ( event && event.type === "mouseover" ) { - target.parents().each(function() { - var parent = $( this ), - blurEvent; - if ( parent.data( "ui-tooltip-open" ) ) { - blurEvent = $.Event( "blur" ); - blurEvent.target = blurEvent.currentTarget = this; - that.close( blurEvent, true ); - } - if ( parent.attr( "title" ) ) { - parent.uniqueId(); - that.parents[ this.id ] = { - element: this, - title: parent.attr( "title" ) - }; - parent.attr( "title", "" ); - } - }); - } - - this._updateContent( target, event ); - }, - - _updateContent: function( target, event ) { - var content, - contentOption = this.options.content, - that = this, - eventType = event ? event.type : null; - - if ( typeof contentOption === "string" ) { - return this._open( event, target, contentOption ); - } - - content = contentOption.call( target[0], function( response ) { - // ignore async response if tooltip was closed already - if ( !target.data( "ui-tooltip-open" ) ) { - return; - } - // IE may instantly serve a cached response for ajax requests - // delay this call to _open so the other call to _open runs first - that._delay(function() { - // jQuery creates a special event for focusin when it doesn't - // exist natively. To improve performance, the native event - // object is reused and the type is changed. Therefore, we can't - // rely on the type being correct after the event finished - // bubbling, so we set it back to the previous value. (#8740) - if ( event ) { - event.type = eventType; - } - this._open( event, target, response ); - }); - }); - if ( content ) { - this._open( event, target, content ); - } - }, - - _open: function( event, target, content ) { - var tooltip, events, delayedShow, - positionOption = $.extend( {}, this.options.position ); - - if ( !content ) { - return; - } - - // Content can be updated multiple times. If the tooltip already - // exists, then just update the content and bail. - tooltip = this._find( target ); - if ( tooltip.length ) { - tooltip.find( ".ui-tooltip-content" ).html( content ); - return; - } - - // if we have a title, clear it to prevent the native tooltip - // we have to check first to avoid defining a title if none exists - // (we don't want to cause an element to start matching [title]) - // - // We use removeAttr only for key events, to allow IE to export the correct - // accessible attributes. For mouse events, set to empty string to avoid - // native tooltip showing up (happens only when removing inside mouseover). - if ( target.is( "[title]" ) ) { - if ( event && event.type === "mouseover" ) { - target.attr( "title", "" ); - } else { - target.removeAttr( "title" ); - } - } - - tooltip = this._tooltip( target ); - addDescribedBy( target, tooltip.attr( "id" ) ); - tooltip.find( ".ui-tooltip-content" ).html( content ); - - function position( event ) { - positionOption.of = event; - if ( tooltip.is( ":hidden" ) ) { - return; - } - tooltip.position( positionOption ); - } - if ( this.options.track && event && /^mouse/.test( event.type ) ) { - this._on( this.document, { - mousemove: position - }); - // trigger once to override element-relative positioning - position( event ); - } else { - tooltip.position( $.extend({ - of: target - }, this.options.position ) ); - } - - tooltip.hide(); - - this._show( tooltip, this.options.show ); - // Handle tracking tooltips that are shown with a delay (#8644). As soon - // as the tooltip is visible, position the tooltip using the most recent - // event. - if ( this.options.show && this.options.show.delay ) { - delayedShow = setInterval(function() { - if ( tooltip.is( ":visible" ) ) { - position( positionOption.of ); - clearInterval( delayedShow ); - } - }, $.fx.interval ); - } - - this._trigger( "open", event, { tooltip: tooltip } ); - - events = { - keyup: function( event ) { - if ( event.keyCode === $.ui.keyCode.ESCAPE ) { - var fakeEvent = $.Event(event); - fakeEvent.currentTarget = target[0]; - this.close( fakeEvent, true ); - } - }, - remove: function() { - this._removeTooltip( tooltip ); - } - }; - if ( !event || event.type === "mouseover" ) { - events.mouseleave = "close"; - } - if ( !event || event.type === "focusin" ) { - events.focusout = "close"; - } - this._on( true, target, events ); - }, - - close: function( event ) { - var that = this, - target = $( event ? event.currentTarget : this.element ), - tooltip = this._find( target ); - - // disabling closes the tooltip, so we need to track when we're closing - // to avoid an infinite loop in case the tooltip becomes disabled on close - if ( this.closing ) { - return; - } - - // only set title if we had one before (see comment in _open()) - if ( target.data( "ui-tooltip-title" ) ) { - target.attr( "title", target.data( "ui-tooltip-title" ) ); - } - - removeDescribedBy( target ); - - tooltip.stop( true ); - this._hide( tooltip, this.options.hide, function() { - that._removeTooltip( $( this ) ); - }); - - target.removeData( "ui-tooltip-open" ); - this._off( target, "mouseleave focusout keyup" ); - // Remove 'remove' binding only on delegated targets - if ( target[0] !== this.element[0] ) { - this._off( target, "remove" ); - } - this._off( this.document, "mousemove" ); - - if ( event && event.type === "mouseleave" ) { - $.each( this.parents, function( id, parent ) { - $( parent.element ).attr( "title", parent.title ); - delete that.parents[ id ]; - }); - } - - this.closing = true; - this._trigger( "close", event, { tooltip: tooltip } ); - this.closing = false; - }, - - _tooltip: function( element ) { - var id = "ui-tooltip-" + increments++, - tooltip = $( "
    " ) - .attr({ - id: id, - role: "tooltip" - }) - .addClass( "ui-tooltip ui-widget ui-corner-all ui-widget-content " + - ( this.options.tooltipClass || "" ) ); - $( "
    " ) - .addClass( "ui-tooltip-content" ) - .appendTo( tooltip ); - tooltip.appendTo( this.document[0].body ); - if ( $.fn.bgiframe ) { - tooltip.bgiframe(); - } - this.tooltips[ id ] = element; - return tooltip; - }, - - _find: function( target ) { - var id = target.data( "ui-tooltip-id" ); - return id ? $( "#" + id ) : $(); - }, - - _removeTooltip: function( tooltip ) { - tooltip.remove(); - delete this.tooltips[ tooltip.attr( "id" ) ]; - }, - - _destroy: function() { - var that = this; - - // close open tooltips - $.each( this.tooltips, function( id, element ) { - // Delegate to close method to handle common cleanup - var event = $.Event( "blur" ); - event.target = event.currentTarget = element[0]; - that.close( event, true ); - - // Remove immediately; destroying an open tooltip doesn't use the - // hide animation - $( "#" + id ).remove(); - - // Restore the title - if ( element.data( "ui-tooltip-title" ) ) { - element.attr( "title", element.data( "ui-tooltip-title" ) ); - element.removeData( "ui-tooltip-title" ); - } - }); - } -}); - -}( jQuery ) ); diff --git a/iliad-stable/Core/Public/javascripts/no_conflict.js b/iliad-stable/Core/Public/javascripts/no_conflict.js deleted file mode 100644 index 82e0791..0000000 --- a/iliad-stable/Core/Public/javascripts/no_conflict.js +++ /dev/null @@ -1,2 +0,0 @@ -jQuery.noConflict(); - diff --git a/iliad-stable/Core/Public/stylesheets/iliad.css b/iliad-stable/Core/Public/stylesheets/iliad.css deleted file mode 100644 index e60325a..0000000 --- a/iliad-stable/Core/Public/stylesheets/iliad.css +++ /dev/null @@ -1,93 +0,0 @@ -body { - background-color: #f4f1f1; - font-family: "Verdana", "DejaVu Sans", sans-serif; - color: #636363; - font-size: 12px; - text-align: center; -} - -img { - border: 0 none -} - -.wrapper { - margin: 0 auto; - text-align: left; - width: 600px; -} - -.logo { - text-align: center; -} - -h1, h2, h3 { - font-weight: normal; -} - -h1 { - color: #3B3B3B; - font-size: 32px; -} - -h2 { - font-size: 22px; -} - -h3 { - font-size: 18px; - margin-top: 5px; - margin-bottom: 5px; -} - -a, a:visited { - color: #660e7b; - font-weight: bold; - text-decoration: none; -} - -a:hover { - color: #111; -} - -table { - margin: 10px; - padding: 10px; - line-height: 1.5em; - border: 1px solid #ccc; - background: #fcfcfc -} - -thead { - font-size: 1.4em -} - -td { - padding-left: 14px; - padding-right: 14px; -} - -pre { - margin: 10px; - padding: 10px; - line-height: 1.5em; - background-color: #fafafa; - border: 1px solid #cef6c9; -} - -input, textarea { - border: 1px solid #444; -} - -.error, .errors { - color: #d51a2c; - font-weight: bold -} - -.errors {margin-bottom: 10px} - -.error input, -.error textarea { - background-color: #f4e5e6; - border: 1px solid #d51a2c} - -.required:after {content: ' *'; color: #d51a2c; font-weight: bold} diff --git a/iliad-stable/Core/Public/stylesheets/images/ui-bg_flat_0_aaaaaa_40x100.png b/iliad-stable/Core/Public/stylesheets/images/ui-bg_flat_0_aaaaaa_40x100.png deleted file mode 100644 index 5b5dab2..0000000 Binary files a/iliad-stable/Core/Public/stylesheets/images/ui-bg_flat_0_aaaaaa_40x100.png and /dev/null differ diff --git a/iliad-stable/Core/Public/stylesheets/images/ui-bg_flat_75_ffffff_40x100.png b/iliad-stable/Core/Public/stylesheets/images/ui-bg_flat_75_ffffff_40x100.png deleted file mode 100644 index ac8b229..0000000 Binary files a/iliad-stable/Core/Public/stylesheets/images/ui-bg_flat_75_ffffff_40x100.png and /dev/null differ diff --git a/iliad-stable/Core/Public/stylesheets/images/ui-bg_glass_55_fbf9ee_1x400.png b/iliad-stable/Core/Public/stylesheets/images/ui-bg_glass_55_fbf9ee_1x400.png deleted file mode 100644 index ad3d634..0000000 Binary files a/iliad-stable/Core/Public/stylesheets/images/ui-bg_glass_55_fbf9ee_1x400.png and /dev/null differ diff --git a/iliad-stable/Core/Public/stylesheets/images/ui-bg_glass_65_ffffff_1x400.png b/iliad-stable/Core/Public/stylesheets/images/ui-bg_glass_65_ffffff_1x400.png deleted file mode 100644 index 42ccba2..0000000 Binary files a/iliad-stable/Core/Public/stylesheets/images/ui-bg_glass_65_ffffff_1x400.png and /dev/null differ diff --git a/iliad-stable/Core/Public/stylesheets/images/ui-bg_glass_75_dadada_1x400.png b/iliad-stable/Core/Public/stylesheets/images/ui-bg_glass_75_dadada_1x400.png deleted file mode 100644 index 5a46b47..0000000 Binary files a/iliad-stable/Core/Public/stylesheets/images/ui-bg_glass_75_dadada_1x400.png and /dev/null differ diff --git a/iliad-stable/Core/Public/stylesheets/images/ui-bg_glass_75_e6e6e6_1x400.png b/iliad-stable/Core/Public/stylesheets/images/ui-bg_glass_75_e6e6e6_1x400.png deleted file mode 100644 index 86c2baa..0000000 Binary files a/iliad-stable/Core/Public/stylesheets/images/ui-bg_glass_75_e6e6e6_1x400.png and /dev/null differ diff --git a/iliad-stable/Core/Public/stylesheets/images/ui-bg_glass_95_fef1ec_1x400.png b/iliad-stable/Core/Public/stylesheets/images/ui-bg_glass_95_fef1ec_1x400.png deleted file mode 100644 index 4443fdc..0000000 Binary files a/iliad-stable/Core/Public/stylesheets/images/ui-bg_glass_95_fef1ec_1x400.png and /dev/null differ diff --git a/iliad-stable/Core/Public/stylesheets/images/ui-bg_highlight-soft_75_cccccc_1x100.png b/iliad-stable/Core/Public/stylesheets/images/ui-bg_highlight-soft_75_cccccc_1x100.png deleted file mode 100644 index 7c9fa6c..0000000 Binary files a/iliad-stable/Core/Public/stylesheets/images/ui-bg_highlight-soft_75_cccccc_1x100.png and /dev/null differ diff --git a/iliad-stable/Core/Public/stylesheets/images/ui-icons_222222_256x240.png b/iliad-stable/Core/Public/stylesheets/images/ui-icons_222222_256x240.png deleted file mode 100644 index b273ff1..0000000 Binary files a/iliad-stable/Core/Public/stylesheets/images/ui-icons_222222_256x240.png and /dev/null differ diff --git a/iliad-stable/Core/Public/stylesheets/images/ui-icons_2e83ff_256x240.png b/iliad-stable/Core/Public/stylesheets/images/ui-icons_2e83ff_256x240.png deleted file mode 100644 index 09d1cdc..0000000 Binary files a/iliad-stable/Core/Public/stylesheets/images/ui-icons_2e83ff_256x240.png and /dev/null differ diff --git a/iliad-stable/Core/Public/stylesheets/images/ui-icons_454545_256x240.png b/iliad-stable/Core/Public/stylesheets/images/ui-icons_454545_256x240.png deleted file mode 100644 index 59bd45b..0000000 Binary files a/iliad-stable/Core/Public/stylesheets/images/ui-icons_454545_256x240.png and /dev/null differ diff --git a/iliad-stable/Core/Public/stylesheets/images/ui-icons_888888_256x240.png b/iliad-stable/Core/Public/stylesheets/images/ui-icons_888888_256x240.png deleted file mode 100644 index 6d02426..0000000 Binary files a/iliad-stable/Core/Public/stylesheets/images/ui-icons_888888_256x240.png and /dev/null differ diff --git a/iliad-stable/Core/Public/stylesheets/images/ui-icons_cd0a0a_256x240.png b/iliad-stable/Core/Public/stylesheets/images/ui-icons_cd0a0a_256x240.png deleted file mode 100644 index 2ab019b..0000000 Binary files a/iliad-stable/Core/Public/stylesheets/images/ui-icons_cd0a0a_256x240.png and /dev/null differ diff --git a/iliad-stable/Core/Public/stylesheets/jquery-ui-1.9.2.css b/iliad-stable/Core/Public/stylesheets/jquery-ui-1.9.2.css deleted file mode 100644 index dd403d8..0000000 --- a/iliad-stable/Core/Public/stylesheets/jquery-ui-1.9.2.css +++ /dev/null @@ -1,474 +0,0 @@ -/*! jQuery UI - v1.9.2 - 2012-11-23 -* http://jqueryui.com -* Includes: jquery.ui.core.css, jquery.ui.accordion.css, jquery.ui.autocomplete.css, jquery.ui.button.css, jquery.ui.datepicker.css, jquery.ui.dialog.css, jquery.ui.menu.css, jquery.ui.progressbar.css, jquery.ui.resizable.css, jquery.ui.selectable.css, jquery.ui.slider.css, jquery.ui.spinner.css, jquery.ui.tabs.css, jquery.ui.tooltip.css, jquery.ui.theme.css -* Copyright 2012 jQuery Foundation and other contributors; Licensed MIT */ - -/* Layout helpers -----------------------------------*/ -.ui-helper-hidden { display: none; } -.ui-helper-hidden-accessible { border: 0; clip: rect(0 0 0 0); height: 1px; margin: -1px; overflow: hidden; padding: 0; position: absolute; width: 1px; } -.ui-helper-reset { margin: 0; padding: 0; border: 0; outline: 0; line-height: 1.3; text-decoration: none; font-size: 100%; list-style: none; } -.ui-helper-clearfix:before, .ui-helper-clearfix:after { content: ""; display: table; } -.ui-helper-clearfix:after { clear: both; } -.ui-helper-clearfix { zoom: 1; } -.ui-helper-zfix { width: 100%; height: 100%; top: 0; left: 0; position: absolute; opacity: 0; filter:Alpha(Opacity=0); } - - -/* Interaction Cues -----------------------------------*/ -.ui-state-disabled { cursor: default !important; } - - -/* Icons -----------------------------------*/ - -/* states and images */ -.ui-icon { display: block; text-indent: -99999px; overflow: hidden; background-repeat: no-repeat; } - - -/* Misc visuals -----------------------------------*/ - -/* Overlays */ -.ui-widget-overlay { position: absolute; top: 0; left: 0; width: 100%; height: 100%; } - -.ui-accordion .ui-accordion-header { display: block; cursor: pointer; position: relative; margin-top: 2px; padding: .5em .5em .5em .7em; zoom: 1; } -.ui-accordion .ui-accordion-icons { padding-left: 2.2em; } -.ui-accordion .ui-accordion-noicons { padding-left: .7em; } -.ui-accordion .ui-accordion-icons .ui-accordion-icons { padding-left: 2.2em; } -.ui-accordion .ui-accordion-header .ui-accordion-header-icon { position: absolute; left: .5em; top: 50%; margin-top: -8px; } -.ui-accordion .ui-accordion-content { padding: 1em 2.2em; border-top: 0; overflow: auto; zoom: 1; } - -.ui-autocomplete { - position: absolute; - top: 0; - left: 0; - cursor: default; -} - -/* workarounds */ -* html .ui-autocomplete { width:1px; } /* without this, the menu expands to 100% in IE6 */ - -.ui-button { display: inline-block; position: relative; padding: 0; margin-right: .1em; cursor: pointer; text-align: center; zoom: 1; overflow: visible; } /* the overflow property removes extra width in IE */ -.ui-button, .ui-button:link, .ui-button:visited, .ui-button:hover, .ui-button:active { text-decoration: none; } -.ui-button-icon-only { width: 2.2em; } /* to make room for the icon, a width needs to be set here */ -button.ui-button-icon-only { width: 2.4em; } /* button elements seem to need a little more width */ -.ui-button-icons-only { width: 3.4em; } -button.ui-button-icons-only { width: 3.7em; } - -/*button text element */ -.ui-button .ui-button-text { display: block; line-height: 1.4; } -.ui-button-text-only .ui-button-text { padding: .4em 1em; } -.ui-button-icon-only .ui-button-text, .ui-button-icons-only .ui-button-text { padding: .4em; text-indent: -9999999px; } -.ui-button-text-icon-primary .ui-button-text, .ui-button-text-icons .ui-button-text { padding: .4em 1em .4em 2.1em; } -.ui-button-text-icon-secondary .ui-button-text, .ui-button-text-icons .ui-button-text { padding: .4em 2.1em .4em 1em; } -.ui-button-text-icons .ui-button-text { padding-left: 2.1em; padding-right: 2.1em; } -/* no icon support for input elements, provide padding by default */ -input.ui-button { padding: .4em 1em; } - -/*button icon element(s) */ -.ui-button-icon-only .ui-icon, .ui-button-text-icon-primary .ui-icon, .ui-button-text-icon-secondary .ui-icon, .ui-button-text-icons .ui-icon, .ui-button-icons-only .ui-icon { position: absolute; top: 50%; margin-top: -8px; } -.ui-button-icon-only .ui-icon { left: 50%; margin-left: -8px; } -.ui-button-text-icon-primary .ui-button-icon-primary, .ui-button-text-icons .ui-button-icon-primary, .ui-button-icons-only .ui-button-icon-primary { left: .5em; } -.ui-button-text-icon-secondary .ui-button-icon-secondary, .ui-button-text-icons .ui-button-icon-secondary, .ui-button-icons-only .ui-button-icon-secondary { right: .5em; } -.ui-button-text-icons .ui-button-icon-secondary, .ui-button-icons-only .ui-button-icon-secondary { right: .5em; } - -/*button sets*/ -.ui-buttonset { margin-right: 7px; } -.ui-buttonset .ui-button { margin-left: 0; margin-right: -.3em; } - -/* workarounds */ -button.ui-button::-moz-focus-inner { border: 0; padding: 0; } /* reset extra padding in Firefox */ - -.ui-datepicker { width: 17em; padding: .2em .2em 0; display: none; } -.ui-datepicker .ui-datepicker-header { position:relative; padding:.2em 0; } -.ui-datepicker .ui-datepicker-prev, .ui-datepicker .ui-datepicker-next { position:absolute; top: 2px; width: 1.8em; height: 1.8em; } -.ui-datepicker .ui-datepicker-prev-hover, .ui-datepicker .ui-datepicker-next-hover { top: 1px; } -.ui-datepicker .ui-datepicker-prev { left:2px; } -.ui-datepicker .ui-datepicker-next { right:2px; } -.ui-datepicker .ui-datepicker-prev-hover { left:1px; } -.ui-datepicker .ui-datepicker-next-hover { right:1px; } -.ui-datepicker .ui-datepicker-prev span, .ui-datepicker .ui-datepicker-next span { display: block; position: absolute; left: 50%; margin-left: -8px; top: 50%; margin-top: -8px; } -.ui-datepicker .ui-datepicker-title { margin: 0 2.3em; line-height: 1.8em; text-align: center; } -.ui-datepicker .ui-datepicker-title select { font-size:1em; margin:1px 0; } -.ui-datepicker select.ui-datepicker-month-year {width: 100%;} -.ui-datepicker select.ui-datepicker-month, -.ui-datepicker select.ui-datepicker-year { width: 49%;} -.ui-datepicker table {width: 100%; font-size: .9em; border-collapse: collapse; margin:0 0 .4em; } -.ui-datepicker th { padding: .7em .3em; text-align: center; font-weight: bold; border: 0; } -.ui-datepicker td { border: 0; padding: 1px; } -.ui-datepicker td span, .ui-datepicker td a { display: block; padding: .2em; text-align: right; text-decoration: none; } -.ui-datepicker .ui-datepicker-buttonpane { background-image: none; margin: .7em 0 0 0; padding:0 .2em; border-left: 0; border-right: 0; border-bottom: 0; } -.ui-datepicker .ui-datepicker-buttonpane button { float: right; margin: .5em .2em .4em; cursor: pointer; padding: .2em .6em .3em .6em; width:auto; overflow:visible; } -.ui-datepicker .ui-datepicker-buttonpane button.ui-datepicker-current { float:left; } - -/* with multiple calendars */ -.ui-datepicker.ui-datepicker-multi { width:auto; } -.ui-datepicker-multi .ui-datepicker-group { float:left; } -.ui-datepicker-multi .ui-datepicker-group table { width:95%; margin:0 auto .4em; } -.ui-datepicker-multi-2 .ui-datepicker-group { width:50%; } -.ui-datepicker-multi-3 .ui-datepicker-group { width:33.3%; } -.ui-datepicker-multi-4 .ui-datepicker-group { width:25%; } -.ui-datepicker-multi .ui-datepicker-group-last .ui-datepicker-header { border-left-width:0; } -.ui-datepicker-multi .ui-datepicker-group-middle .ui-datepicker-header { border-left-width:0; } -.ui-datepicker-multi .ui-datepicker-buttonpane { clear:left; } -.ui-datepicker-row-break { clear:both; width:100%; font-size:0em; } - -/* RTL support */ -.ui-datepicker-rtl { direction: rtl; } -.ui-datepicker-rtl .ui-datepicker-prev { right: 2px; left: auto; } -.ui-datepicker-rtl .ui-datepicker-next { left: 2px; right: auto; } -.ui-datepicker-rtl .ui-datepicker-prev:hover { right: 1px; left: auto; } -.ui-datepicker-rtl .ui-datepicker-next:hover { left: 1px; right: auto; } -.ui-datepicker-rtl .ui-datepicker-buttonpane { clear:right; } -.ui-datepicker-rtl .ui-datepicker-buttonpane button { float: left; } -.ui-datepicker-rtl .ui-datepicker-buttonpane button.ui-datepicker-current { float:right; } -.ui-datepicker-rtl .ui-datepicker-group { float:right; } -.ui-datepicker-rtl .ui-datepicker-group-last .ui-datepicker-header { border-right-width:0; border-left-width:1px; } -.ui-datepicker-rtl .ui-datepicker-group-middle .ui-datepicker-header { border-right-width:0; border-left-width:1px; } - -/* IE6 IFRAME FIX (taken from datepicker 1.5.3 */ -.ui-datepicker-cover { - position: absolute; /*must have*/ - z-index: -1; /*must have*/ - filter: mask(); /*must have*/ - top: -4px; /*must have*/ - left: -4px; /*must have*/ - width: 200px; /*must have*/ - height: 200px; /*must have*/ -} -.ui-dialog { position: absolute; top: 0; left: 0; padding: .2em; width: 300px; overflow: hidden; } -.ui-dialog .ui-dialog-titlebar { padding: .4em 1em; position: relative; } -.ui-dialog .ui-dialog-title { float: left; margin: .1em 16px .1em 0; } -.ui-dialog .ui-dialog-titlebar-close { position: absolute; right: .3em; top: 50%; width: 19px; margin: -10px 0 0 0; padding: 1px; height: 18px; } -.ui-dialog .ui-dialog-titlebar-close span { display: block; margin: 1px; } -.ui-dialog .ui-dialog-titlebar-close:hover, .ui-dialog .ui-dialog-titlebar-close:focus { padding: 0; } -.ui-dialog .ui-dialog-content { position: relative; border: 0; padding: .5em 1em; background: none; overflow: auto; zoom: 1; } -.ui-dialog .ui-dialog-buttonpane { text-align: left; border-width: 1px 0 0 0; background-image: none; margin: .5em 0 0 0; padding: .3em 1em .5em .4em; } -.ui-dialog .ui-dialog-buttonpane .ui-dialog-buttonset { float: right; } -.ui-dialog .ui-dialog-buttonpane button { margin: .5em .4em .5em 0; cursor: pointer; } -.ui-dialog .ui-resizable-se { width: 14px; height: 14px; right: 3px; bottom: 3px; } -.ui-draggable .ui-dialog-titlebar { cursor: move; } - -.ui-menu { list-style:none; padding: 2px; margin: 0; display:block; outline: none; } -.ui-menu .ui-menu { margin-top: -3px; position: absolute; } -.ui-menu .ui-menu-item { margin: 0; padding: 0; zoom: 1; width: 100%; } -.ui-menu .ui-menu-divider { margin: 5px -2px 5px -2px; height: 0; font-size: 0; line-height: 0; border-width: 1px 0 0 0; } -.ui-menu .ui-menu-item a { text-decoration: none; display: block; padding: 2px .4em; line-height: 1.5; zoom: 1; font-weight: normal; } -.ui-menu .ui-menu-item a.ui-state-focus, -.ui-menu .ui-menu-item a.ui-state-active { font-weight: normal; margin: -1px; } - -.ui-menu .ui-state-disabled { font-weight: normal; margin: .4em 0 .2em; line-height: 1.5; } -.ui-menu .ui-state-disabled a { cursor: default; } - -/* icon support */ -.ui-menu-icons { position: relative; } -.ui-menu-icons .ui-menu-item a { position: relative; padding-left: 2em; } - -/* left-aligned */ -.ui-menu .ui-icon { position: absolute; top: .2em; left: .2em; } - -/* right-aligned */ -.ui-menu .ui-menu-icon { position: static; float: right; } - -.ui-progressbar { height:2em; text-align: left; overflow: hidden; } -.ui-progressbar .ui-progressbar-value {margin: -1px; height:100%; } -.ui-resizable { position: relative;} -.ui-resizable-handle { position: absolute;font-size: 0.1px; display: block; } -.ui-resizable-disabled .ui-resizable-handle, .ui-resizable-autohide .ui-resizable-handle { display: none; } -.ui-resizable-n { cursor: n-resize; height: 7px; width: 100%; top: -5px; left: 0; } -.ui-resizable-s { cursor: s-resize; height: 7px; width: 100%; bottom: -5px; left: 0; } -.ui-resizable-e { cursor: e-resize; width: 7px; right: -5px; top: 0; height: 100%; } -.ui-resizable-w { cursor: w-resize; width: 7px; left: -5px; top: 0; height: 100%; } -.ui-resizable-se { cursor: se-resize; width: 12px; height: 12px; right: 1px; bottom: 1px; } -.ui-resizable-sw { cursor: sw-resize; width: 9px; height: 9px; left: -5px; bottom: -5px; } -.ui-resizable-nw { cursor: nw-resize; width: 9px; height: 9px; left: -5px; top: -5px; } -.ui-resizable-ne { cursor: ne-resize; width: 9px; height: 9px; right: -5px; top: -5px;} -.ui-selectable-helper { position: absolute; z-index: 100; border:1px dotted black; } - -.ui-slider { position: relative; text-align: left; } -.ui-slider .ui-slider-handle { position: absolute; z-index: 2; width: 1.2em; height: 1.2em; cursor: default; } -.ui-slider .ui-slider-range { position: absolute; z-index: 1; font-size: .7em; display: block; border: 0; background-position: 0 0; } - -.ui-slider-horizontal { height: .8em; } -.ui-slider-horizontal .ui-slider-handle { top: -.3em; margin-left: -.6em; } -.ui-slider-horizontal .ui-slider-range { top: 0; height: 100%; } -.ui-slider-horizontal .ui-slider-range-min { left: 0; } -.ui-slider-horizontal .ui-slider-range-max { right: 0; } - -.ui-slider-vertical { width: .8em; height: 100px; } -.ui-slider-vertical .ui-slider-handle { left: -.3em; margin-left: 0; margin-bottom: -.6em; } -.ui-slider-vertical .ui-slider-range { left: 0; width: 100%; } -.ui-slider-vertical .ui-slider-range-min { bottom: 0; } -.ui-slider-vertical .ui-slider-range-max { top: 0; } -.ui-spinner { position:relative; display: inline-block; overflow: hidden; padding: 0; vertical-align: middle; } -.ui-spinner-input { border: none; background: none; padding: 0; margin: .2em 0; vertical-align: middle; margin-left: .4em; margin-right: 22px; } -.ui-spinner-button { width: 16px; height: 50%; font-size: .5em; padding: 0; margin: 0; text-align: center; position: absolute; cursor: default; display: block; overflow: hidden; right: 0; } -.ui-spinner a.ui-spinner-button { border-top: none; border-bottom: none; border-right: none; } /* more specificity required here to overide default borders */ -.ui-spinner .ui-icon { position: absolute; margin-top: -8px; top: 50%; left: 0; } /* vertical centre icon */ -.ui-spinner-up { top: 0; } -.ui-spinner-down { bottom: 0; } - -/* TR overrides */ -.ui-spinner .ui-icon-triangle-1-s { - /* need to fix icons sprite */ - background-position:-65px -16px; -} - -.ui-tabs { position: relative; padding: .2em; zoom: 1; } /* position: relative prevents IE scroll bug (element with position: relative inside container with overflow: auto appear as "fixed") */ -.ui-tabs .ui-tabs-nav { margin: 0; padding: .2em .2em 0; } -.ui-tabs .ui-tabs-nav li { list-style: none; float: left; position: relative; top: 0; margin: 1px .2em 0 0; border-bottom: 0; padding: 0; white-space: nowrap; } -.ui-tabs .ui-tabs-nav li a { float: left; padding: .5em 1em; text-decoration: none; } -.ui-tabs .ui-tabs-nav li.ui-tabs-active { margin-bottom: -1px; padding-bottom: 1px; } -.ui-tabs .ui-tabs-nav li.ui-tabs-active a, .ui-tabs .ui-tabs-nav li.ui-state-disabled a, .ui-tabs .ui-tabs-nav li.ui-tabs-loading a { cursor: text; } -.ui-tabs .ui-tabs-nav li a, .ui-tabs-collapsible .ui-tabs-nav li.ui-tabs-active a { cursor: pointer; } /* first selector in group seems obsolete, but required to overcome bug in Opera applying cursor: text overall if defined elsewhere... */ -.ui-tabs .ui-tabs-panel { display: block; border-width: 0; padding: 1em 1.4em; background: none; } - -.ui-tooltip { - padding: 8px; - position: absolute; - z-index: 9999; - max-width: 300px; - -webkit-box-shadow: 0 0 5px #aaa; - box-shadow: 0 0 5px #aaa; -} -/* Fades and background-images don't work well together in IE6, drop the image */ -* html .ui-tooltip { - background-image: none; -} -body .ui-tooltip { border-width: 2px; } - -/* Component containers -----------------------------------*/ -.ui-widget { font-family: Verdana,Arial,sans-serif/*{ffDefault}*/; font-size: 1.1em/*{fsDefault}*/; } -.ui-widget .ui-widget { font-size: 1em; } -.ui-widget input, .ui-widget select, .ui-widget textarea, .ui-widget button { font-family: Verdana,Arial,sans-serif/*{ffDefault}*/; font-size: 1em; } -.ui-widget-content { border: 1px solid #aaaaaa/*{borderColorContent}*/; background: #ffffff/*{bgColorContent}*/ url(images/ui-bg_flat_75_ffffff_40x100.png)/*{bgImgUrlContent}*/ 50%/*{bgContentXPos}*/ 50%/*{bgContentYPos}*/ repeat-x/*{bgContentRepeat}*/; color: #222222/*{fcContent}*/; } -.ui-widget-content a { color: #222222/*{fcContent}*/; } -.ui-widget-header { border: 1px solid #aaaaaa/*{borderColorHeader}*/; background: #cccccc/*{bgColorHeader}*/ url(images/ui-bg_highlight-soft_75_cccccc_1x100.png)/*{bgImgUrlHeader}*/ 50%/*{bgHeaderXPos}*/ 50%/*{bgHeaderYPos}*/ repeat-x/*{bgHeaderRepeat}*/; color: #222222/*{fcHeader}*/; font-weight: bold; } -.ui-widget-header a { color: #222222/*{fcHeader}*/; } - -/* Interaction states -----------------------------------*/ -.ui-state-default, .ui-widget-content .ui-state-default, .ui-widget-header .ui-state-default { border: 1px solid #d3d3d3/*{borderColorDefault}*/; background: #e6e6e6/*{bgColorDefault}*/ url(images/ui-bg_glass_75_e6e6e6_1x400.png)/*{bgImgUrlDefault}*/ 50%/*{bgDefaultXPos}*/ 50%/*{bgDefaultYPos}*/ repeat-x/*{bgDefaultRepeat}*/; font-weight: normal/*{fwDefault}*/; color: #555555/*{fcDefault}*/; } -.ui-state-default a, .ui-state-default a:link, .ui-state-default a:visited { color: #555555/*{fcDefault}*/; text-decoration: none; } -.ui-state-hover, .ui-widget-content .ui-state-hover, .ui-widget-header .ui-state-hover, .ui-state-focus, .ui-widget-content .ui-state-focus, .ui-widget-header .ui-state-focus { border: 1px solid #999999/*{borderColorHover}*/; background: #dadada/*{bgColorHover}*/ url(images/ui-bg_glass_75_dadada_1x400.png)/*{bgImgUrlHover}*/ 50%/*{bgHoverXPos}*/ 50%/*{bgHoverYPos}*/ repeat-x/*{bgHoverRepeat}*/; font-weight: normal/*{fwDefault}*/; color: #212121/*{fcHover}*/; } -.ui-state-hover a, .ui-state-hover a:hover, .ui-state-hover a:link, .ui-state-hover a:visited { color: #212121/*{fcHover}*/; text-decoration: none; } -.ui-state-active, .ui-widget-content .ui-state-active, .ui-widget-header .ui-state-active { border: 1px solid #aaaaaa/*{borderColorActive}*/; background: #ffffff/*{bgColorActive}*/ url(images/ui-bg_glass_65_ffffff_1x400.png)/*{bgImgUrlActive}*/ 50%/*{bgActiveXPos}*/ 50%/*{bgActiveYPos}*/ repeat-x/*{bgActiveRepeat}*/; font-weight: normal/*{fwDefault}*/; color: #212121/*{fcActive}*/; } -.ui-state-active a, .ui-state-active a:link, .ui-state-active a:visited { color: #212121/*{fcActive}*/; text-decoration: none; } - -/* Interaction Cues -----------------------------------*/ -.ui-state-highlight, .ui-widget-content .ui-state-highlight, .ui-widget-header .ui-state-highlight {border: 1px solid #fcefa1/*{borderColorHighlight}*/; background: #fbf9ee/*{bgColorHighlight}*/ url(images/ui-bg_glass_55_fbf9ee_1x400.png)/*{bgImgUrlHighlight}*/ 50%/*{bgHighlightXPos}*/ 50%/*{bgHighlightYPos}*/ repeat-x/*{bgHighlightRepeat}*/; color: #363636/*{fcHighlight}*/; } -.ui-state-highlight a, .ui-widget-content .ui-state-highlight a,.ui-widget-header .ui-state-highlight a { color: #363636/*{fcHighlight}*/; } -.ui-state-error, .ui-widget-content .ui-state-error, .ui-widget-header .ui-state-error {border: 1px solid #cd0a0a/*{borderColorError}*/; background: #fef1ec/*{bgColorError}*/ url(images/ui-bg_glass_95_fef1ec_1x400.png)/*{bgImgUrlError}*/ 50%/*{bgErrorXPos}*/ 50%/*{bgErrorYPos}*/ repeat-x/*{bgErrorRepeat}*/; color: #cd0a0a/*{fcError}*/; } -.ui-state-error a, .ui-widget-content .ui-state-error a, .ui-widget-header .ui-state-error a { color: #cd0a0a/*{fcError}*/; } -.ui-state-error-text, .ui-widget-content .ui-state-error-text, .ui-widget-header .ui-state-error-text { color: #cd0a0a/*{fcError}*/; } -.ui-priority-primary, .ui-widget-content .ui-priority-primary, .ui-widget-header .ui-priority-primary { font-weight: bold; } -.ui-priority-secondary, .ui-widget-content .ui-priority-secondary, .ui-widget-header .ui-priority-secondary { opacity: .7; filter:Alpha(Opacity=70); font-weight: normal; } -.ui-state-disabled, .ui-widget-content .ui-state-disabled, .ui-widget-header .ui-state-disabled { opacity: .35; filter:Alpha(Opacity=35); background-image: none; } -.ui-state-disabled .ui-icon { filter:Alpha(Opacity=35); } /* For IE8 - See #6059 */ - -/* Icons -----------------------------------*/ - -/* states and images */ -.ui-icon { width: 16px; height: 16px; background-image: url(images/ui-icons_222222_256x240.png)/*{iconsContent}*/; } -.ui-widget-content .ui-icon {background-image: url(images/ui-icons_222222_256x240.png)/*{iconsContent}*/; } -.ui-widget-header .ui-icon {background-image: url(images/ui-icons_222222_256x240.png)/*{iconsHeader}*/; } -.ui-state-default .ui-icon { background-image: url(images/ui-icons_888888_256x240.png)/*{iconsDefault}*/; } -.ui-state-hover .ui-icon, .ui-state-focus .ui-icon {background-image: url(images/ui-icons_454545_256x240.png)/*{iconsHover}*/; } -.ui-state-active .ui-icon {background-image: url(images/ui-icons_454545_256x240.png)/*{iconsActive}*/; } -.ui-state-highlight .ui-icon {background-image: url(images/ui-icons_2e83ff_256x240.png)/*{iconsHighlight}*/; } -.ui-state-error .ui-icon, .ui-state-error-text .ui-icon {background-image: url(images/ui-icons_cd0a0a_256x240.png)/*{iconsError}*/; } - -/* positioning */ -.ui-icon-carat-1-n { background-position: 0 0; } -.ui-icon-carat-1-ne { background-position: -16px 0; } -.ui-icon-carat-1-e { background-position: -32px 0; } -.ui-icon-carat-1-se { background-position: -48px 0; } -.ui-icon-carat-1-s { background-position: -64px 0; } -.ui-icon-carat-1-sw { background-position: -80px 0; } -.ui-icon-carat-1-w { background-position: -96px 0; } -.ui-icon-carat-1-nw { background-position: -112px 0; } -.ui-icon-carat-2-n-s { background-position: -128px 0; } -.ui-icon-carat-2-e-w { background-position: -144px 0; } -.ui-icon-triangle-1-n { background-position: 0 -16px; } -.ui-icon-triangle-1-ne { background-position: -16px -16px; } -.ui-icon-triangle-1-e { background-position: -32px -16px; } -.ui-icon-triangle-1-se { background-position: -48px -16px; } -.ui-icon-triangle-1-s { background-position: -64px -16px; } -.ui-icon-triangle-1-sw { background-position: -80px -16px; } -.ui-icon-triangle-1-w { background-position: -96px -16px; } -.ui-icon-triangle-1-nw { background-position: -112px -16px; } -.ui-icon-triangle-2-n-s { background-position: -128px -16px; } -.ui-icon-triangle-2-e-w { background-position: -144px -16px; } -.ui-icon-arrow-1-n { background-position: 0 -32px; } -.ui-icon-arrow-1-ne { background-position: -16px -32px; } -.ui-icon-arrow-1-e { background-position: -32px -32px; } -.ui-icon-arrow-1-se { background-position: -48px -32px; } -.ui-icon-arrow-1-s { background-position: -64px -32px; } -.ui-icon-arrow-1-sw { background-position: -80px -32px; } -.ui-icon-arrow-1-w { background-position: -96px -32px; } -.ui-icon-arrow-1-nw { background-position: -112px -32px; } -.ui-icon-arrow-2-n-s { background-position: -128px -32px; } -.ui-icon-arrow-2-ne-sw { background-position: -144px -32px; } -.ui-icon-arrow-2-e-w { background-position: -160px -32px; } -.ui-icon-arrow-2-se-nw { background-position: -176px -32px; } -.ui-icon-arrowstop-1-n { background-position: -192px -32px; } -.ui-icon-arrowstop-1-e { background-position: -208px -32px; } -.ui-icon-arrowstop-1-s { background-position: -224px -32px; } -.ui-icon-arrowstop-1-w { background-position: -240px -32px; } -.ui-icon-arrowthick-1-n { background-position: 0 -48px; } -.ui-icon-arrowthick-1-ne { background-position: -16px -48px; } -.ui-icon-arrowthick-1-e { background-position: -32px -48px; } -.ui-icon-arrowthick-1-se { background-position: -48px -48px; } -.ui-icon-arrowthick-1-s { background-position: -64px -48px; } -.ui-icon-arrowthick-1-sw { background-position: -80px -48px; } -.ui-icon-arrowthick-1-w { background-position: -96px -48px; } -.ui-icon-arrowthick-1-nw { background-position: -112px -48px; } -.ui-icon-arrowthick-2-n-s { background-position: -128px -48px; } -.ui-icon-arrowthick-2-ne-sw { background-position: -144px -48px; } -.ui-icon-arrowthick-2-e-w { background-position: -160px -48px; } -.ui-icon-arrowthick-2-se-nw { background-position: -176px -48px; } -.ui-icon-arrowthickstop-1-n { background-position: -192px -48px; } -.ui-icon-arrowthickstop-1-e { background-position: -208px -48px; } -.ui-icon-arrowthickstop-1-s { background-position: -224px -48px; } -.ui-icon-arrowthickstop-1-w { background-position: -240px -48px; } -.ui-icon-arrowreturnthick-1-w { background-position: 0 -64px; } -.ui-icon-arrowreturnthick-1-n { background-position: -16px -64px; } -.ui-icon-arrowreturnthick-1-e { background-position: -32px -64px; } -.ui-icon-arrowreturnthick-1-s { background-position: -48px -64px; } -.ui-icon-arrowreturn-1-w { background-position: -64px -64px; } -.ui-icon-arrowreturn-1-n { background-position: -80px -64px; } -.ui-icon-arrowreturn-1-e { background-position: -96px -64px; } -.ui-icon-arrowreturn-1-s { background-position: -112px -64px; } -.ui-icon-arrowrefresh-1-w { background-position: -128px -64px; } -.ui-icon-arrowrefresh-1-n { background-position: -144px -64px; } -.ui-icon-arrowrefresh-1-e { background-position: -160px -64px; } -.ui-icon-arrowrefresh-1-s { background-position: -176px -64px; } -.ui-icon-arrow-4 { background-position: 0 -80px; } -.ui-icon-arrow-4-diag { background-position: -16px -80px; } -.ui-icon-extlink { background-position: -32px -80px; } -.ui-icon-newwin { background-position: -48px -80px; } -.ui-icon-refresh { background-position: -64px -80px; } -.ui-icon-shuffle { background-position: -80px -80px; } -.ui-icon-transfer-e-w { background-position: -96px -80px; } -.ui-icon-transferthick-e-w { background-position: -112px -80px; } -.ui-icon-folder-collapsed { background-position: 0 -96px; } -.ui-icon-folder-open { background-position: -16px -96px; } -.ui-icon-document { background-position: -32px -96px; } -.ui-icon-document-b { background-position: -48px -96px; } -.ui-icon-note { background-position: -64px -96px; } -.ui-icon-mail-closed { background-position: -80px -96px; } -.ui-icon-mail-open { background-position: -96px -96px; } -.ui-icon-suitcase { background-position: -112px -96px; } -.ui-icon-comment { background-position: -128px -96px; } -.ui-icon-person { background-position: -144px -96px; } -.ui-icon-print { background-position: -160px -96px; } -.ui-icon-trash { background-position: -176px -96px; } -.ui-icon-locked { background-position: -192px -96px; } -.ui-icon-unlocked { background-position: -208px -96px; } -.ui-icon-bookmark { background-position: -224px -96px; } -.ui-icon-tag { background-position: -240px -96px; } -.ui-icon-home { background-position: 0 -112px; } -.ui-icon-flag { background-position: -16px -112px; } -.ui-icon-calendar { background-position: -32px -112px; } -.ui-icon-cart { background-position: -48px -112px; } -.ui-icon-pencil { background-position: -64px -112px; } -.ui-icon-clock { background-position: -80px -112px; } -.ui-icon-disk { background-position: -96px -112px; } -.ui-icon-calculator { background-position: -112px -112px; } -.ui-icon-zoomin { background-position: -128px -112px; } -.ui-icon-zoomout { background-position: -144px -112px; } -.ui-icon-search { background-position: -160px -112px; } -.ui-icon-wrench { background-position: -176px -112px; } -.ui-icon-gear { background-position: -192px -112px; } -.ui-icon-heart { background-position: -208px -112px; } -.ui-icon-star { background-position: -224px -112px; } -.ui-icon-link { background-position: -240px -112px; } -.ui-icon-cancel { background-position: 0 -128px; } -.ui-icon-plus { background-position: -16px -128px; } -.ui-icon-plusthick { background-position: -32px -128px; } -.ui-icon-minus { background-position: -48px -128px; } -.ui-icon-minusthick { background-position: -64px -128px; } -.ui-icon-close { background-position: -80px -128px; } -.ui-icon-closethick { background-position: -96px -128px; } -.ui-icon-key { background-position: -112px -128px; } -.ui-icon-lightbulb { background-position: -128px -128px; } -.ui-icon-scissors { background-position: -144px -128px; } -.ui-icon-clipboard { background-position: -160px -128px; } -.ui-icon-copy { background-position: -176px -128px; } -.ui-icon-contact { background-position: -192px -128px; } -.ui-icon-image { background-position: -208px -128px; } -.ui-icon-video { background-position: -224px -128px; } -.ui-icon-script { background-position: -240px -128px; } -.ui-icon-alert { background-position: 0 -144px; } -.ui-icon-info { background-position: -16px -144px; } -.ui-icon-notice { background-position: -32px -144px; } -.ui-icon-help { background-position: -48px -144px; } -.ui-icon-check { background-position: -64px -144px; } -.ui-icon-bullet { background-position: -80px -144px; } -.ui-icon-radio-on { background-position: -96px -144px; } -.ui-icon-radio-off { background-position: -112px -144px; } -.ui-icon-pin-w { background-position: -128px -144px; } -.ui-icon-pin-s { background-position: -144px -144px; } -.ui-icon-play { background-position: 0 -160px; } -.ui-icon-pause { background-position: -16px -160px; } -.ui-icon-seek-next { background-position: -32px -160px; } -.ui-icon-seek-prev { background-position: -48px -160px; } -.ui-icon-seek-end { background-position: -64px -160px; } -.ui-icon-seek-start { background-position: -80px -160px; } -/* ui-icon-seek-first is deprecated, use ui-icon-seek-start instead */ -.ui-icon-seek-first { background-position: -80px -160px; } -.ui-icon-stop { background-position: -96px -160px; } -.ui-icon-eject { background-position: -112px -160px; } -.ui-icon-volume-off { background-position: -128px -160px; } -.ui-icon-volume-on { background-position: -144px -160px; } -.ui-icon-power { background-position: 0 -176px; } -.ui-icon-signal-diag { background-position: -16px -176px; } -.ui-icon-signal { background-position: -32px -176px; } -.ui-icon-battery-0 { background-position: -48px -176px; } -.ui-icon-battery-1 { background-position: -64px -176px; } -.ui-icon-battery-2 { background-position: -80px -176px; } -.ui-icon-battery-3 { background-position: -96px -176px; } -.ui-icon-circle-plus { background-position: 0 -192px; } -.ui-icon-circle-minus { background-position: -16px -192px; } -.ui-icon-circle-close { background-position: -32px -192px; } -.ui-icon-circle-triangle-e { background-position: -48px -192px; } -.ui-icon-circle-triangle-s { background-position: -64px -192px; } -.ui-icon-circle-triangle-w { background-position: -80px -192px; } -.ui-icon-circle-triangle-n { background-position: -96px -192px; } -.ui-icon-circle-arrow-e { background-position: -112px -192px; } -.ui-icon-circle-arrow-s { background-position: -128px -192px; } -.ui-icon-circle-arrow-w { background-position: -144px -192px; } -.ui-icon-circle-arrow-n { background-position: -160px -192px; } -.ui-icon-circle-zoomin { background-position: -176px -192px; } -.ui-icon-circle-zoomout { background-position: -192px -192px; } -.ui-icon-circle-check { background-position: -208px -192px; } -.ui-icon-circlesmall-plus { background-position: 0 -208px; } -.ui-icon-circlesmall-minus { background-position: -16px -208px; } -.ui-icon-circlesmall-close { background-position: -32px -208px; } -.ui-icon-squaresmall-plus { background-position: -48px -208px; } -.ui-icon-squaresmall-minus { background-position: -64px -208px; } -.ui-icon-squaresmall-close { background-position: -80px -208px; } -.ui-icon-grip-dotted-vertical { background-position: 0 -224px; } -.ui-icon-grip-dotted-horizontal { background-position: -16px -224px; } -.ui-icon-grip-solid-vertical { background-position: -32px -224px; } -.ui-icon-grip-solid-horizontal { background-position: -48px -224px; } -.ui-icon-gripsmall-diagonal-se { background-position: -64px -224px; } -.ui-icon-grip-diagonal-se { background-position: -80px -224px; } - - -/* Misc visuals -----------------------------------*/ - -/* Corner radius */ -.ui-corner-all, .ui-corner-top, .ui-corner-left, .ui-corner-tl { -moz-border-radius-topleft: 4px/*{cornerRadius}*/; -webkit-border-top-left-radius: 4px/*{cornerRadius}*/; -khtml-border-top-left-radius: 4px/*{cornerRadius}*/; border-top-left-radius: 4px/*{cornerRadius}*/; } -.ui-corner-all, .ui-corner-top, .ui-corner-right, .ui-corner-tr { -moz-border-radius-topright: 4px/*{cornerRadius}*/; -webkit-border-top-right-radius: 4px/*{cornerRadius}*/; -khtml-border-top-right-radius: 4px/*{cornerRadius}*/; border-top-right-radius: 4px/*{cornerRadius}*/; } -.ui-corner-all, .ui-corner-bottom, .ui-corner-left, .ui-corner-bl { -moz-border-radius-bottomleft: 4px/*{cornerRadius}*/; -webkit-border-bottom-left-radius: 4px/*{cornerRadius}*/; -khtml-border-bottom-left-radius: 4px/*{cornerRadius}*/; border-bottom-left-radius: 4px/*{cornerRadius}*/; } -.ui-corner-all, .ui-corner-bottom, .ui-corner-right, .ui-corner-br { -moz-border-radius-bottomright: 4px/*{cornerRadius}*/; -webkit-border-bottom-right-radius: 4px/*{cornerRadius}*/; -khtml-border-bottom-right-radius: 4px/*{cornerRadius}*/; border-bottom-right-radius: 4px/*{cornerRadius}*/; } - -/* Overlays */ -.ui-widget-overlay { background: #aaaaaa/*{bgColorOverlay}*/ url(images/ui-bg_flat_0_aaaaaa_40x100.png)/*{bgImgUrlOverlay}*/ 50%/*{bgOverlayXPos}*/ 50%/*{bgOverlayYPos}*/ repeat-x/*{bgOverlayRepeat}*/; opacity: .3;filter:Alpha(Opacity=30)/*{opacityOverlay}*/; } -.ui-widget-shadow { margin: -8px/*{offsetTopShadow}*/ 0 0 -8px/*{offsetLeftShadow}*/; padding: 8px/*{thicknessShadow}*/; background: #aaaaaa/*{bgColorShadow}*/ url(images/ui-bg_flat_0_aaaaaa_40x100.png)/*{bgImgUrlShadow}*/ 50%/*{bgShadowXPos}*/ 50%/*{bgShadowYPos}*/ repeat-x/*{bgShadowRepeat}*/; opacity: .3;filter:Alpha(Opacity=30)/*{opacityShadow}*/; -moz-border-radius: 8px/*{cornerRadiusShadow}*/; -khtml-border-radius: 8px/*{cornerRadiusShadow}*/; -webkit-border-radius: 8px/*{cornerRadiusShadow}*/; border-radius: 8px/*{cornerRadiusShadow}*/; } \ No newline at end of file diff --git a/iliad-stable/Core/RequestHandlers/ILApplicationHandler.st b/iliad-stable/Core/RequestHandlers/ILApplicationHandler.st deleted file mode 100644 index f4034b4..0000000 --- a/iliad-stable/Core/RequestHandlers/ILApplicationHandler.st +++ /dev/null @@ -1,122 +0,0 @@ -"====================================================================== -| -| Iliad.ILApplicationHandler class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILRequestHandler subclass: ILApplicationHandler [ - | actions | - - - - initialize [ - - super initialize. - actions := OrderedCollection new - ] - - evaluateActions [ - - self getActionsFromRequest. - (actions asSortedCollection: [:a :b | a key asInteger < b key asInteger]) - do: [:each | each evaluate] - ] - - handleRequest [ - - self session isExpired ifTrue: [self session onExpire]. - self isRequestValid - ifTrue: [self evaluateActions] - ifFalse: [ILRedirectHandler new handleRequest]. - self shouldReturnEmptyResponse ifTrue: [ - self returnResponse: ILResponse ok]. - self shouldRespondInJson ifTrue: [ - ILJsonHandler new handleRequest]. - self shouldRedirect - ifTrue: [ILRedirectHandler new handleRequest] - ifFalse: [self produceResponse] - ] - - produceResponse [ - - self respond: [:response | - self addAllowHeaderTo: response. - self session useCookies ifTrue: [self addCookieHeaderTo: response]. - self session refreshOnBacktrack ifTrue: [self addNoCacheHeaderTo: response]] - ] - - isRequestValid [ - - ^self context previousStateRegistry notNil - or: [self request actionField isNil and: [self request isGet]] - ] - - shouldRedirect [ - - ^self request isTypeOfRequestForRedirect - ] - - shouldRespondInJson [ - - ^self request isTypeOfRequestForJson - ] - - shouldReturnEmptyResponse [ - - ^self request ajaxUploadField notNil - ] - - newResponse [ - - ^self application asResponse - ] - - getActionsFromRequest [ - - | action | - actions := OrderedCollection new. - self request isGet ifTrue: [ - | actionField | - actionField := self request actionField. - action := self session actionAt: actionField. - action ifNotNil: [actions add: action]]. - self request isPost ifTrue: [ - self request fields associations do: [:asso | - (action := self session actionAt: asso value) ifNil: [ - action := self session actionAt: asso key. - action ifNotNil: [action value: asso value]]. - action ifNotNil: [actions add: action]]] - ] -] diff --git a/iliad-stable/Core/RequestHandlers/ILDirectory.st b/iliad-stable/Core/RequestHandlers/ILDirectory.st deleted file mode 100644 index bd2906e..0000000 --- a/iliad-stable/Core/RequestHandlers/ILDirectory.st +++ /dev/null @@ -1,10 +0,0 @@ -ILObject subclass: ILDirectory [ - - - - - fileContentsFor: aFilename [ - - self subclassResponsibility - ] -] diff --git a/iliad-stable/Core/RequestHandlers/ILErrorHandler.st b/iliad-stable/Core/RequestHandlers/ILErrorHandler.st deleted file mode 100644 index 10b86dd..0000000 --- a/iliad-stable/Core/RequestHandlers/ILErrorHandler.st +++ /dev/null @@ -1,173 +0,0 @@ -"====================================================================== -| -| Iliad.ILErrorHandler class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILRequestHandler subclass: ILErrorHandler [ - | error | - - - -protocol. - -When errors occur, the framework with handle them differently depending on -the application mode: -- in deployment mode, it will respond an error 500; -- in verbose mode, it will also respond an error 500, but with error details; -- in debug mode, a debugger window will be opened on the error;'> - - ILErrorHandler class [ - | mode | - - mode [ - - ^mode ifNil: [mode := #verbose] - ] - - mode: aSymbol [ - - mode := aSymbol - ] - - verboseMode [ - - self mode: #verbose - ] - - debugMode [ - - self mode: #debug - ] - - deploymentMode [ - - self mode: #deployment - ] - - ] - - error [ - - ^error - ] - - error: anError [ - - error := anError - ] - - mode [ - - ^self class mode - ] - - newResponse [ - - ^ILResponse new - status: 500; - yourself - ] - - produceResponse [ - - self isDebugMode ifTrue: [ - self produceDebugResponse]. - self isVerboseMode ifTrue: [ - self produceVerboseResponse]. - self isDeploymentMode ifTrue: [ - self produceDeploymentResponse] - ] - - produceDeploymentResponse [ - - self respond: [:response | - response nextPutAll: '

    Error 500: Internal server error

    '] - ] - - produceDebugResponse [ - - self error resignalAsUnhandled: self error messageText - ] - - produceVerboseResponse [ - - | info | - info := WriteStream on: ''. - self respond: [:response || page e | - response nextPutAll: (String streamContents: [:stream | - page := ILHTMLPage new. - page body h1: 'Internal Error'; - h2: self error description; - h3: self error messageText. - self error examineOn: info. - info nextPut: Character cr. - self error resumeContext backtraceOn: info. - page body pre: info contents. - Transcript show: info contents; cr. - page build printHtmlOn: stream])] - ] - - - isDebugMode [ - - ^self mode = #debug - ] - - isVerboseMode [ - - ^self mode = #verbose - ] - - isDeploymentMode [ - - ^self isDebugMode not and: [ - self isVerboseMode not] - ] -] - -Exception extend [ - resumeContext [ - ^resumeBlock outerContext home - ] -] diff --git a/iliad-stable/Core/RequestHandlers/ILFileHandler.st b/iliad-stable/Core/RequestHandlers/ILFileHandler.st deleted file mode 100644 index 6df214c..0000000 --- a/iliad-stable/Core/RequestHandlers/ILFileHandler.st +++ /dev/null @@ -1,559 +0,0 @@ -"====================================================================== -| -| Iliad.ILFileHandler class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILRequestHandler subclass: ILFileHandler [ - | file | - - - - - MimeTypes := nil. - Directories := nil. - - ILFileHandler class >> defaultMimeType [ - - ^'application/octet-stream' - ] - - ILFileHandler class >> defaultMimeTypes [ - - ^ #( - '%' 'application/x-trash' - '323' 'text/h323' - 'abw' 'application/x-abiword' - 'ai' 'application/postscript' - 'aif' 'audio/x-aiff' - 'aifc' 'audio/x-aiff' - 'aiff' 'audio/x-aiff' - 'alc' 'chemical/x-alchemy' - 'art' 'image/x-jg' - 'asc' 'text/plain' - 'asf' 'video/x-ms-asf' - 'asn' 'chemical/x-ncbi-asn1-spec' - 'aso' 'chemical/x-ncbi-asn1-binary' - 'asx' 'video/x-ms-asf' - 'au' 'audio/basic' - 'avi' 'video/x-msvideo' - 'b' 'chemical/x-molconn-Z' - 'bak' 'application/x-trash' - 'bat' 'application/x-msdos-program' - 'bcpio' 'application/x-bcpio' - 'bib' 'text/x-bibtex' - 'bin' 'application/octet-stream' - 'bmp' 'image/x-ms-bmp' - 'book' 'application/x-maker' - 'bsd' 'chemical/x-crossfire' - 'c' 'text/x-csrc' - 'c++' 'text/x-c++src' - 'c3d' 'chemical/x-chem3d' - 'cac' 'chemical/x-cache' - 'cache' 'chemical/x-cache' - 'cascii' 'chemical/x-cactvs-binary' - 'cat' 'application/vnd.ms-pki.seccat' - 'cbin' 'chemical/x-cactvs-binary' - 'cc' 'text/x-c++src' - 'cdf' 'application/x-cdf' - 'cdr' 'image/x-coreldraw' - 'cdt' 'image/x-coreldrawtemplate' - 'cdx' 'chemical/x-cdx' - 'cdy' 'application/vnd.cinderella' - 'cef' 'chemical/x-cxf' - 'cer' 'chemical/x-cerius' - 'chm' 'chemical/x-chemdraw' - 'chrt' 'application/x-kchart' - 'cif' 'chemical/x-cif' - 'class' 'application/java-vm' - 'cls' 'text/x-tex' - 'cmdf' 'chemical/x-cmdf' - 'cml' 'chemical/x-cml' - 'cod' 'application/vnd.rim.cod' - 'com' 'application/x-msdos-program' - 'cpa' 'chemical/x-compass' - 'cpio' 'application/x-cpio' - 'cpp' 'text/x-c++src' - 'cpt' 'image/x-corelphotopaint' - 'crl' 'application/x-pkcs7-crl' - 'crt' 'application/x-x509-ca-cert' - 'csf' 'chemical/x-cache-csf' - 'csh' 'text/x-csh' - 'csm' 'chemical/x-csml' - 'csml' 'chemical/x-csml' - 'css' 'text/css' - 'csv' 'text/comma-separated-values' - 'ctab' 'chemical/x-cactvs-binary' - 'ctx' 'chemical/x-ctx' - 'cu' 'application/cu-seeme' - 'cub' 'chemical/x-gaussian-cube' - 'cxf' 'chemical/x-cxf' - 'cxx' 'text/x-c++src' - 'dat' 'chemical/x-mopac-input' - 'dcr' 'application/x-director' - 'deb' 'application/x-debian-package' - 'dif' 'video/dv' - 'diff' 'text/plain' - 'dir' 'application/x-director' - 'djv' 'image/vnd.djvu' - 'djvu' 'image/vnd.djvu' - 'dl' 'video/dl' - 'dll' 'application/x-msdos-program' - 'dmg' 'application/x-apple-diskimage' - 'dms' 'application/x-dms' - 'doc' 'application/msword' - 'dot' 'application/msword' - 'dv' 'video/dv' - 'dvi' 'application/x-dvi' - 'dx' 'chemical/x-jcamp-dx' - 'dxr' 'application/x-director' - 'emb' 'chemical/x-embl-dl-nucleotide' - 'embl' 'chemical/x-embl-dl-nucleotide' - 'ent' 'chemical/x-pdb' - 'eps' 'application/postscript' - 'etx' 'text/x-setext' - 'exe' 'application/x-msdos-program' - 'ez' 'application/andrew-inset' - 'fb' 'application/x-maker' - 'fbdoc' 'application/x-maker' - 'fch' 'chemical/x-gaussian-checkpoint' - 'fchk' 'chemical/x-gaussian-checkpoint' - 'fig' 'application/x-xfig' - 'flac' 'application/x-flac' - 'fli' 'video/fli' - 'fm' 'application/x-maker' - 'frame' 'application/x-maker' - 'frm' 'application/x-maker' - 'gal' 'chemical/x-gaussian-log' - 'gam' 'chemical/x-gamess-input' - 'gamin' 'chemical/x-gamess-input' - 'gau' 'chemical/x-gaussian-input' - 'gcd' 'text/x-pcs-gcd' - 'gcf' 'application/x-graphing-calculator' - 'gcg' 'chemical/x-gcg8-sequence' - 'gen' 'chemical/x-genbank' - 'gf' 'application/x-tex-gf' - 'gif' 'image/gif' - 'gjc' 'chemical/x-gaussian-input' - 'gjf' 'chemical/x-gaussian-input' - 'gl' 'video/gl' - 'gnumeric' 'application/x-gnumeric' - 'gpt' 'chemical/x-mopac-graph' - 'gsf' 'application/x-font' - 'gsm' 'audio/x-gsm' - 'gtar' 'application/x-gtar' - 'h' 'text/x-chdr' - 'h++' 'text/x-c++hdr' - 'hdf' 'application/x-hdf' - 'hh' 'text/x-c++hdr' - 'hin' 'chemical/x-hin' - 'hpp' 'text/x-c++hdr' - 'hqx' 'application/mac-binhex40' - 'hs' 'text/x-haskell' - 'hta' 'application/hta' - 'htc' 'text/x-component' - 'htm' 'text/html' - 'html' 'text/html' - 'hxx' 'text/x-c++hdr' - 'ica' 'application/x-ica' - 'ice' 'x-conference/x-cooltalk' - 'ico' 'image/x-icon' - 'ics' 'text/calendar' - 'icz' 'text/calendar' - 'ief' 'image/ief' - 'iges' 'model/iges' - 'igs' 'model/iges' - 'iii' 'application/x-iphone' - 'inp' 'chemical/x-gamess-input' - 'ins' 'application/x-internet-signup' - 'iso' 'application/x-iso9660-image' - 'isp' 'application/x-internet-signup' - 'ist' 'chemical/x-isostar' - 'istr' 'chemical/x-isostar' - 'jad' 'text/vnd.sun.j2me.app-descriptor' - 'jar' 'application/java-archive' - 'java' 'text/x-java' - 'jdx' 'chemical/x-jcamp-dx' - 'jmz' 'application/x-jmol' - 'jng' 'image/x-jng' - 'jnlp' 'application/x-java-jnlp-file' - 'jpe' 'image/jpeg' - 'jpeg' 'image/jpeg' - 'jpg' 'image/jpeg' - 'js' 'application/x-javascript' - 'kar' 'audio/midi' - 'key' 'application/pgp-keys' - 'kil' 'application/x-killustrator' - 'kin' 'chemical/x-kinemage' - 'kpr' 'application/x-kpresenter' - 'kpt' 'application/x-kpresenter' - 'ksp' 'application/x-kspread' - 'kwd' 'application/x-kword' - 'kwt' 'application/x-kword' - 'latex' 'application/x-latex' - 'lha' 'application/x-lha' - 'lhs' 'text/x-literate-haskell' - 'lsf' 'video/x-la-asf' - 'lsx' 'video/x-la-asf' - 'ltx' 'text/x-tex' - 'lzh' 'application/x-lzh' - 'lzx' 'application/x-lzx' - 'm3u' 'audio/x-mpegurl' - 'm4a' 'audio/mpeg' - 'maker' 'application/x-maker' - 'man' 'application/x-troff-man' - 'mcif' 'chemical/x-mmcif' - 'mcm' 'chemical/x-macmolecule' - 'mdb' 'application/msaccess' - 'me' 'application/x-troff-me' - 'mesh' 'model/mesh' - 'mid' 'audio/midi' - 'midi' 'audio/midi' - 'mif' 'application/x-mif' - 'mm' 'application/x-freemind' - 'mmd' 'chemical/x-macromodel-input' - 'mmf' 'application/vnd.smaf' - 'mml' 'text/mathml' - 'mmod' 'chemical/x-macromodel-input' - 'mng' 'video/x-mng' - 'moc' 'text/x-moc' - 'mol' 'chemical/x-mdl-molfile' - 'mol2' 'chemical/x-mol2' - 'moo' 'chemical/x-mopac-out' - 'mop' 'chemical/x-mopac-input' - 'mopcrt' 'chemical/x-mopac-input' - 'mov' 'video/quicktime' - 'movie' 'video/x-sgi-movie' - 'mp2' 'audio/mpeg' - 'mp3' 'audio/mpeg' - 'mp4' 'video/mp4' - 'mpc' 'chemical/x-mopac-input' - 'mpe' 'video/mpeg' - 'mpeg' 'video/mpeg' - 'mpega' 'audio/mpeg' - 'mpg' 'video/mpeg' - 'mpga' 'audio/mpeg' - 'ms' 'application/x-troff-ms' - 'msh' 'model/mesh' - 'msi' 'application/x-msi' - 'mvb' 'chemical/x-mopac-vib' - 'mxu' 'video/vnd.mpegurl' - 'nb' 'application/mathematica' - 'nc' 'application/x-netcdf' - 'nwc' 'application/x-nwc' - 'o' 'application/x-object' - 'oda' 'application/oda' - 'odb' 'application/vnd.oasis.opendocument.database' - 'odc' 'application/vnd.oasis.opendocument.chart' - 'odf' 'application/vnd.oasis.opendocument.formula' - 'odg' 'application/vnd.oasis.opendocument.graphics' - 'odi' 'application/vnd.oasis.opendocument.image' - 'odm' 'application/vnd.oasis.opendocument.text-master' - 'odp' 'application/vnd.oasis.opendocument.presentation' - 'ods' 'application/vnd.oasis.opendocument.spreadsheet' - 'odt' 'application/vnd.oasis.opendocument.text' - 'ogg' 'application/ogg' - 'old' 'application/x-trash' - 'oth' 'application/vnd.oasis.opendocument.text-web' - 'oza' 'application/x-oz-application' - 'p' 'text/x-pascal' - 'p7r' 'application/x-pkcs7-certreqresp' - 'pac' 'application/x-ns-proxy-autoconfig' - 'pas' 'text/x-pascal' - 'pat' 'image/x-coreldrawpattern' - 'pbm' 'image/x-portable-bitmap' - 'pcf' 'application/x-font' - 'pcf.Z' 'application/x-font' - 'pcx' 'image/pcx' - 'pdb' 'chemical/x-pdb' - 'pdf' 'application/pdf' - 'pfa' 'application/x-font' - 'pfb' 'application/x-font' - 'pgm' 'image/x-portable-graymap' - 'pgn' 'application/x-chess-pgn' - 'pgp' 'application/pgp-signature' - 'pk' 'application/x-tex-pk' - 'pl' 'text/x-perl' - 'pls' 'audio/x-scpls' - 'pm' 'text/x-perl' - 'png' 'image/png' - 'pnm' 'image/x-portable-anymap' - 'pot' 'text/plain' - 'ppm' 'image/x-portable-pixmap' - 'pps' 'application/vnd.ms-powerpoint' - 'ppt' 'application/vnd.ms-powerpoint' - 'prf' 'application/pics-rules' - 'prt' 'chemical/x-ncbi-asn1-ascii' - 'ps' 'application/postscript' - 'psd' 'image/x-photoshop' - 'psp' 'text/x-psp' - 'py' 'text/x-python' - 'pyc' 'application/x-python-code' - 'pyo' 'application/x-python-code' - 'qt' 'video/quicktime' - 'qtl' 'application/x-quicktimeplayer' - 'ra' 'audio/x-realaudio' - 'ram' 'audio/x-pn-realaudio' - 'rar' 'application/rar' - 'ras' 'image/x-cmu-raster' - 'rd' 'chemical/x-mdl-rdfile' - 'rdf' 'application/rdf+xml' - 'rgb' 'image/x-rgb' - 'rm' 'audio/x-pn-realaudio' - 'roff' 'application/x-troff' - 'ros' 'chemical/x-rosdal' - 'rpm' 'application/x-redhat-package-manager' - 'rss' 'application/rss+xml' - 'rtf' 'text/rtf' - 'rtx' 'text/richtext' - 'rxn' 'chemical/x-mdl-rxnfile' - 'sct' 'text/scriptlet' - 'sd' 'chemical/x-mdl-sdfile' - 'sd2' 'audio/x-sd2' - 'sda' 'application/vnd.stardivision.draw' - 'sdc' 'application/vnd.stardivision.calc' - 'sdd' 'application/vnd.stardivision.impress' - 'sdf' 'chemical/x-mdl-sdfile' - 'sdp' 'application/vnd.stardivision.impress' - 'sdw' 'application/vnd.stardivision.writer' - 'ser' 'application/java-serialized-object' - 'sgf' 'application/x-go-sgf' - 'sgl' 'application/vnd.stardivision.writer-global' - 'sh' 'text/x-sh' - 'shar' 'application/x-shar' - 'shtml' 'text/html' - 'sid' 'audio/prs.sid' - 'sik' 'application/x-trash' - 'silo' 'model/mesh' - 'sis' 'application/vnd.symbian.install' - 'sit' 'application/x-stuffit' - 'skd' 'application/x-koan' - 'skm' 'application/x-koan' - 'skp' 'application/x-koan' - 'skt' 'application/x-koan' - 'smf' 'application/vnd.stardivision.math' - 'smi' 'application/smil' - 'smil' 'application/smil' - 'snd' 'audio/basic' - 'spc' 'chemical/x-galactic-spc' - 'spl' 'application/x-futuresplash' - 'src' 'application/x-wais-source' - 'stc' 'application/vnd.sun.xml.calc.template' - 'std' 'application/vnd.sun.xml.draw.template' - 'sti' 'application/vnd.sun.xml.impress.template' - 'stl' 'application/vnd.ms-pki.stl' - 'stw' 'application/vnd.sun.xml.writer.template' - 'sty' 'text/x-tex' - 'sv4cpio' 'application/x-sv4cpio' - 'sv4crc' 'application/x-sv4crc' - 'svg' 'image/svg+xml' - 'svgz' 'image/svg+xml' - 'sw' 'chemical/x-swissprot' - 'swf' 'application/x-shockwave-flash' - 'swfl' 'application/x-shockwave-flash' - 'sxc' 'application/vnd.sun.xml.calc' - 'sxd' 'application/vnd.sun.xml.draw' - 'sxg' 'application/vnd.sun.xml.writer.global' - 'sxi' 'application/vnd.sun.xml.impress' - 'sxm' 'application/vnd.sun.xml.math' - 'sxw' 'application/vnd.sun.xml.writer' - 't' 'application/x-troff' - 'tar' 'application/x-tar' - 'taz' 'application/x-gtar' - 'tcl' 'text/x-tcl' - 'tex' 'text/x-tex' - 'texi' 'application/x-texinfo' - 'texinfo' 'application/x-texinfo' - 'text' 'text/plain' - 'tgf' 'chemical/x-mdl-tgf' - 'tgz' 'application/x-gtar' - 'tif' 'image/tiff' - 'tiff' 'image/tiff' - 'tk' 'text/x-tcl' - 'tm' 'text/texmacs' - 'torrent' 'application/x-bittorrent' - 'tr' 'application/x-troff' - 'ts' 'text/texmacs' - 'tsp' 'application/dsptype' - 'tsv' 'text/tab-separated-values' - 'txt' 'text/plain' - 'udeb' 'application/x-debian-package' - 'uls' 'text/iuls' - 'ustar' 'application/x-ustar' - 'val' 'chemical/x-ncbi-asn1-binary' - 'vcd' 'application/x-cdlink' - 'vcf' 'text/x-vcard' - 'vcs' 'text/x-vcalendar' - 'vmd' 'chemical/x-vmd' - 'vms' 'chemical/x-vamas-iso14976' - 'vor' 'application/vnd.stardivision.writer' - 'vrm' 'x-world/x-vrml' - 'vrml' 'x-world/x-vrml' - 'vsd' 'application/vnd.visio' - 'wad' 'application/x-doom' - 'wav' 'audio/x-wav' - 'wax' 'audio/x-ms-wax' - 'wbmp' 'image/vnd.wap.wbmp' - 'wbxml' 'application/vnd.wap.wbxml' - 'wk' 'application/x-123' - 'wm' 'video/x-ms-wm' - 'wma' 'audio/x-ms-wma' - 'wmd' 'application/x-ms-wmd' - 'wml' 'text/vnd.wap.wml' - 'wmlc' 'application/vnd.wap.wmlc' - 'wmls' 'text/vnd.wap.wmlscript' - 'wmlsc' 'application/vnd.wap.wmlscriptc' - 'wmv' 'video/x-ms-wmv' - 'wmx' 'video/x-ms-wmx' - 'wmz' 'application/x-ms-wmz' - 'wp5' 'application/wordperfect5.1' - 'wpd' 'application/wordperfect' - 'wrl' 'x-world/x-vrml' - 'wsc' 'text/scriptlet' - 'wvx' 'video/x-ms-wvx' - 'wz' 'application/x-wingz' - 'xbm' 'image/x-xbitmap' - 'xcf' 'application/x-xcf' - 'xht' 'application/xhtml+xml' - 'xhtml' 'application/xhtml+xml' - 'xlb' 'application/vnd.ms-excel' - 'xls' 'application/vnd.ms-excel' - 'xlt' 'application/vnd.ms-excel' - 'xml' 'application/xml' - 'xpi' 'application/x-xpinstall' - 'xpm' 'image/x-xpixmap' - 'xsl' 'application/xml' - 'xtel' 'chemical/x-xtel' - 'xul' 'application/vnd.mozilla.xul+xml' - 'xwd' 'image/x-xwindowdump' - 'xyz' 'chemical/x-xyz' - 'zip' 'application/zip' - 'zmt' 'chemical/x-mopac-input' - '~' 'application/x-trash' - ) - ] - - ILFileHandler class >> mimeTypeFor: aString [ - - ^self mimeTypes at: aString ifAbsent: [self defaultMimeType] - ] - - ILFileHandler class >> mimeTypes [ - - MimeTypes ifNil: [self initMimeTypes]. - ^MimeTypes - ] - - ILFileHandler class >> directories [ - - ^Directories ifNil: [Directories := OrderedCollection new] - ] - - ILFileHandler class >> directories: aCollection [ - - Directories := aCollection - ] - - ILFileHandler class >> addDirectory: aDirectory [ - - self directories add: aDirectory - ] - - ILFileHandler class >> initMimeTypes [ - - MimeTypes := Dictionary new. - 1 to: self defaultMimeTypes size by: 2 do: [:index | - MimeTypes - at: (self defaultMimeTypes at: index) - put: (self defaultMimeTypes at: index + 1)] - ] - - ILFileHandler class >> isBinary: aFilename [ - - | tokens type | - tokens := (ILFileHandler mimeTypeFor: (aFilename copyAfterLast: $.)) subStrings: '/'. - type := tokens first. - type = 'text' ifTrue: [^false]. - type = 'application' ifFalse: [^true]. - tokens size = 1 ifTrue: [^true]. - ^(tokens second subStrings: '+') noneSatisfy: [:each | - #('x-javascript' 'xml') includes: each] - ] - - directories [ - - ^self class directories - ] - - mimeTypeFor: aFilename [ - - ^self class mimeTypeFor: (aFilename copyAfterLast: $.) - ] - - newResponse [ - - ^ILResponse ok - ] - - - handleRequest [ - - file := self fileContentsFor: self request url greaseString. - file isNil ifTrue: [ - ILDispatchError signal]. - super handleRequest - ] - - produceResponse [ - - self respond: [:response || stream | - stream := file readStream. - [response nextPutAll: stream contents] - ensure: [stream close]. - response contentType: (self mimeTypeFor: self request url greaseString). - self addAllowHeaderTo: response. - self addCacheHeaderTo: response] - ] - - fileContentsFor: aFileName [ - "Try to find a file with in one of the directories" - - aFileName isEmpty ifTrue: [^nil]. - self directories do: [:each || fileContents | - fileContents := (each fileContentsFor: aFileName). - (fileContents notNil) ifTrue: [^fileContents]]. - ^nil - ] -] diff --git a/iliad-stable/Core/RequestHandlers/ILJsonHandler.st b/iliad-stable/Core/RequestHandlers/ILJsonHandler.st deleted file mode 100644 index d6bfd72..0000000 --- a/iliad-stable/Core/RequestHandlers/ILJsonHandler.st +++ /dev/null @@ -1,117 +0,0 @@ -"====================================================================== -| -| Iliad.ILJsonHandler class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILRequestHandler subclass: ILJsonHandler [ - | jsonContents widgets scripts head | - - - - - initialize [ - - super initialize. - jsonContents := Dictionary new. - head := OrderedCollection new. - widgets := Dictionary new - ] - - produceResponse [ - - self respond: [:response | - self shouldRedirect - ifTrue: [ - jsonContents - at: 'redirect' - put: self session redirectUrl greaseString] - ifFalse: [ - self shouldUpdateApplication - ifFalse: [ - self updateHead. - self updateWidgets] - ifTrue: [self updateApplication]]. - response nextPutAll: (String streamContents: [:stream | - jsonContents printJsonOn: stream]). - self session clearRedirectUrl. - self addNoCacheHeaderTo: response] - ] - - shouldRedirect [ - - ^self session redirectUrl notNil - ] - - shouldUpdateApplication [ - - ^self request hashLocationField notNil and: [ - self request actionField isNil] - ] - - newResponse [ - - ^ILResponse ok - contentType: 'application/json'; - yourself - ] - - updateHead [ - - | headElement | - headElement := ILElement new. - self session dirtyWidgets do: [:each | each buildHead: headElement]. - headElement childrenDo: [:each | - (self application page head children includes: each) ifFalse: [ - head add: each]]. - jsonContents at: 'head' put: head - ] - - updateWidgets [ - - self session dirtyWidgets do: [:each || e | - e := each build. - widgets at: each id put: e]. - jsonContents - at: 'widgets' put: widgets - ] - - updateApplication [ - - jsonContents - at: 'application' - put: self application build - ] -] diff --git a/iliad-stable/Core/RequestHandlers/ILMemoryDirectory.st b/iliad-stable/Core/RequestHandlers/ILMemoryDirectory.st deleted file mode 100644 index 2721631..0000000 --- a/iliad-stable/Core/RequestHandlers/ILMemoryDirectory.st +++ /dev/null @@ -1,130 +0,0 @@ -ILDirectory subclass: ILMemoryDirectory [ - - - - - ILMemoryDirectory class [ - - addAllFilesIn: aPathString [ - - "adds all files in the directory specified by aPathString to the current file library" - (Grease.GRPlatform current filesIn: aPathString) do: [:each | self addFileAt: each] - ] - - addFileAt: aPath [ - - "adds the file specified by aFilename to the current file library" - self - addFileAt: aPath - contents: (Grease.GRPlatform current - contentsOfFile: aPath - binary: (ILFileHandler isBinary: aPath)) - ] - - addFileAt: aPath contents: aByteArrayOrString [ - - self - addFileNamed: (Grease.GRPlatform current localNameOf: aPath) - contents: aByteArrayOrString - ] - - addFileNamed: aFilename contents: aByteArrayOrString [ - - | selector | - selector := self convertToSelector: aFilename. - (ILFileHandler isBinary: aFilename) - ifTrue: [self compileBinary: aByteArrayOrString selector: selector] - ifFalse: [self compileText: aByteArrayOrString selector: selector] - ] - - compileText: aByteArrayOrString selector: aSymbol [ - "Compiles aByteArrayOrString into a method named aSymbol that returns aByteArrayOrString as a string literal." - - - Grease.GRPlatform current - compile: (Grease.GRPlatform current asMethodReturningString: aByteArrayOrString named: aSymbol) - into: self - classified: self methodCategory - ] - - compileBinary: aByteArrayOrString selector: aSymbol [ - "Compiles aByteArrayOrString into a method named aSymbol that returns aByteArrayOrString as a string literal." - - - Grease.GRPlatform current - compile: (Grease.GRPlatform current asMethodReturningByteArray: aByteArrayOrString named: aSymbol) - into: self - classified: 'files' - ] - - convertToSelector: aString [ - - | mainPart extension | - mainPart := (aString copyUpToLast: $.) - reject: [:each | each isAlphaNumeric not]. - mainPart isEmpty not ifTrue: [ - [mainPart first isDigit] - whileTrue: [mainPart := mainPart allButFirst]]. - extension := (aString copyAfterLast: $.) asLowercase capitalized. - ^(mainPart , extension) asSymbol - ] - ] - - fileContentsFor: aString [ - - | fileSelector | - fileSelector := self convertToSelector: (self adjustPath: aString). - (self isFileSelector: fileSelector) ifFalse: [^nil]. - ^(self perform: fileSelector) - ] - - path [ - "answer the base path of the memory directory" - - - ^self subclassResponsibility - ] - - fileSelectors [ - - ^self class selectors select: [:each | - self isFileSelector: each] - ] - - isFileSelector: aSelector [ - "Only methods in 'files' protocol are allowed to be served as files" - - - ^(self class whichCategoryIncludesSelector: aSelector) = 'files' - ] - - adjustPath: aString [ - - ^aString copyReplacingRegex: '^\/', self path, '\/' with: '' - ] - - convertToSelector: aString [ - - ^self class convertToSelector: aString - ] - - removeFile: aFilename [ - - Grease.GRPlatform current - removeSelector: (self asSelector: aFilename) - from: self class - ] - - deployFiles [ - "Write to disk the files that the receiver use to serve as methods. - The files are stored in a subfolder named like the classname of the receiver in a subfolder of Smalltalk image folder." - - - Grease.GRPlatform current ensureExistenceOfFolder: self path. - self fileSelectors do: [:each | - Grease.GRPlatform current - write: (self perform: each) - toFile: (self asFilename: each) - inFolder: self path] - ] -] diff --git a/iliad-stable/Core/RequestHandlers/ILNotFoundHandler.st b/iliad-stable/Core/RequestHandlers/ILNotFoundHandler.st deleted file mode 100644 index 7d27af4..0000000 --- a/iliad-stable/Core/RequestHandlers/ILNotFoundHandler.st +++ /dev/null @@ -1,57 +0,0 @@ -"====================================================================== -| -| Iliad.ILNotFoundHandler class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILRequestHandler subclass: ILNotFoundHandler [ - - - - produceResponse [ - - self respond: [:response | - response - nextPutAll: '

    404 Not Found: '; - nextPutAll: self request url greaseString; - nextPutAll: '

    '] - ] - - newResponse [ - - ^ILResponse notFound - ] -] - diff --git a/iliad-stable/Core/RequestHandlers/ILRedirectHandler.st b/iliad-stable/Core/RequestHandlers/ILRedirectHandler.st deleted file mode 100644 index 689f025..0000000 --- a/iliad-stable/Core/RequestHandlers/ILRedirectHandler.st +++ /dev/null @@ -1,70 +0,0 @@ -"====================================================================== -| -| Iliad.ILRedirectHandler class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILRequestHandler subclass: ILRedirectHandler [ - - - - produceResponse [ - - self setRedirectUrl. - self shouldRespondInJson ifTrue: [ - ILJsonHandler new handleRequest]. - self respond: [:response | - response redirectTo: self session redirectUrl greaseString. - self session clearRedirectUrl. - self addCookieHeaderTo: response] - ] - - shouldRespondInJson [ - - ^self request isTypeOfRequestForJson - ] - - setRedirectUrl [ - - self session redirectUrl ifNil: [ - self session redirectUrl: self context baseUrl greaseString] - ] - - newResponse [ - - ^ILResponse redirect - ] -] - diff --git a/iliad-stable/Core/RequestHandlers/ILRequestHandler.st b/iliad-stable/Core/RequestHandlers/ILRequestHandler.st deleted file mode 100644 index fa8d7d1..0000000 --- a/iliad-stable/Core/RequestHandlers/ILRequestHandler.st +++ /dev/null @@ -1,107 +0,0 @@ -"====================================================================== -| -| Iliad.ILRequestHandler class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILObject subclass: ILRequestHandler [ - - - - handleRequest [ - - self produceResponse - ] - - produceResponse [ - - self respond: [:response | ] - ] - - respond: aBlock [ - - | response | - response := self newResponse. - aBlock value: response. - self returnResponse: response - ] - - returnResponse: aResponse [ - - ILResponseNotification new - response: aResponse; - signal - ] - - newResponse [ - - self subclassResponsibility - ] - - addCacheHeaderTo: aResponse [ - - aResponse - headerAt: 'expires' - put: ((Grease.GRPrinter rfc822WithTimeZone: 'GMT') - print: (DateTime fromSeconds: DateTime now asSeconds + (24*3600*365))) - ] - - addAllowHeaderTo: aResponse [ - - | methods | - methods := 'OPTIONS,GET,HEAD,POST,DELETE,TRACE,PROPFIND,PROPPATCH,MKCOL,PUT,COPY,MOVE,LOCK,UNLOCK'. - aResponse headerAt: 'Allow' put: methods - ] - - addCookieHeaderTo: aResponse [ - - aResponse - addCookie: (ILCookie new - key: self session sessionManager cookieName; - value: self session id; - expireIn: (Duration days: 600); - yourself) - ] - - addNoCacheHeaderTo: aResponse [ - aResponse - headerAt: 'expires' - put: ((Grease.GRPrinter rfc822WithTimeZone: 'GMT') print: DateTime now). - aResponse headerAt: 'Cache-Control' put: 'no-store, no-cache, must-revalidate' - ] -] diff --git a/iliad-stable/Core/RequestHandlers/ILResponseNotification.st b/iliad-stable/Core/RequestHandlers/ILResponseNotification.st deleted file mode 100644 index caf3667..0000000 --- a/iliad-stable/Core/RequestHandlers/ILResponseNotification.st +++ /dev/null @@ -1,54 +0,0 @@ -"====================================================================== -| -| Iliad.ILResponseNotification class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -Notification subclass: ILResponseNotification [ - | response | - - - - response [ - - ^response - ] - - response: aResponse [ - - response := aResponse - ] -] - diff --git a/iliad-stable/Core/Sessions/ILAction.st b/iliad-stable/Core/Sessions/ILAction.st deleted file mode 100644 index e11c5a9..0000000 --- a/iliad-stable/Core/Sessions/ILAction.st +++ /dev/null @@ -1,84 +0,0 @@ -"====================================================================== -| -| Iliad.ILAction class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILObject subclass: ILAction [ - | key block value | - - - - - block [ - - ^block - ] - - block: aBlock [ - - block := aBlock - ] - - key [ - - ^key - ] - - key: anId [ - - key := anId - ] - - value [ - - ^value - ] - - value: anObject [ - - value := anObject - ] - - evaluate [ - - self block ifNil: [^nil]. - ^self block valueWithPossibleArguments: (Array with: self value) - ] - - respondOn: aResponse [ - - ^self value respondOn: aResponse - ] -] diff --git a/iliad-stable/Core/Sessions/ILActionRegistry.st b/iliad-stable/Core/Sessions/ILActionRegistry.st deleted file mode 100644 index e3a28ad..0000000 --- a/iliad-stable/Core/Sessions/ILActionRegistry.st +++ /dev/null @@ -1,81 +0,0 @@ -"====================================================================== -| -| Iliad.ILActionRegistry class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - -ILObject subclass: ILActionRegistry [ - | actions | - - - - - actionAt: aKey [ - - ^self actions - at: aKey - ifAbsent: [nil] - ] - - actions [ - - ^actions ifNil: [actions := Dictionary new] - ] - - evaluateActionKey: aString [ - - | action | - action := self actionAt: aString. - ^action - ifNil: [nil] - ifNotNil: [action evaluate] - ] - - register: anAction [ - - self actions at: anAction key put: anAction - ] - - unregister: anAction [ - - self actions - removeKey: anAction key - ifAbsent: [nil] - ] - - unregisterAllActions [ - - actions := nil - ] -] diff --git a/iliad-stable/Core/Sessions/ILContext.st b/iliad-stable/Core/Sessions/ILContext.st deleted file mode 100644 index 5fd9891..0000000 --- a/iliad-stable/Core/Sessions/ILContext.st +++ /dev/null @@ -1,129 +0,0 @@ -"====================================================================== -| -| Iliad.ILContext class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILObject subclass: ILContext [ - - | request router session urlBuilder previousStateRegistry stateRegistry builtWidgets attributes | - - >context'> - - router [ - - ^router ifNil: [router := ILRouter new] - ] - - application [ - - ^self router application - ] - - urlBuilder [ - - ^urlBuilder ifNil: [urlBuilder := ILUrlBuilder new] - ] - - baseUrl [ - - ^self urlBuilder baseUrl - ] - - request [ - - ^request - ] - - request: aRequest [ - - request := aRequest - ] - - session [ - - ^session - ] - - session: aSession [ - - session := aSession - ] - - stateRegistry [ - - ^stateRegistry ifNil: [ - stateRegistry := (self session stateRegistryAt: self request stateField) - ifNil: [self session newStateRegistry]] - ] - - previousStateRegistry [ - - ^previousStateRegistry ifNil: [ - previousStateRegistry := (self session stateRegistryAt: self request stateField) copy] - ] - - builtWidgets [ - - ^builtWidgets ifNil: [builtWidgets := OrderedCollection new] - ] - - attributes [ - - ^attributes ifNil: [attributes := Dictionary new] - ] - - attributeAt: aKey [ - - ^self attributes at: aKey ifAbsent: [nil] - ] - - attributeAt: aKey put: anObject [ - - self attributes at: aKey put: anObject - ] - - addBuiltWidget: aWidget [ - - self builtWidgets add: aWidget - ] -] - diff --git a/iliad-stable/Core/Sessions/ILCurrentContext.st b/iliad-stable/Core/Sessions/ILCurrentContext.st deleted file mode 100644 index 6b2820b..0000000 --- a/iliad-stable/Core/Sessions/ILCurrentContext.st +++ /dev/null @@ -1,43 +0,0 @@ -"====================================================================== -| -| Iliad.ILCurrentContext class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILDynamicVariable subclass: ILCurrentContext [ - - -] - diff --git a/iliad-stable/Core/Sessions/ILSession.st b/iliad-stable/Core/Sessions/ILSession.st deleted file mode 100644 index 02ae2b2..0000000 --- a/iliad-stable/Core/Sessions/ILSession.st +++ /dev/null @@ -1,393 +0,0 @@ -"====================================================================== -| -| Iliad.ILSession class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILObject subclass: ILSession [ - | id preferences others timestamps expired redirectUrl applications actionRegistry stateRegistries nextId | - - - - - initialize [ - - super initialize. - expired := false. - self setCreatedTimestamp; - setRandomId - ] - - clearRedirectUrl [ - - redirectUrl := nil - ] - - clearActionRegistry [ - - actionRegistry := nil - ] - - clearStateRegistries [ - - stateRegistries := nil - ] - - id [ - - ^id - ] - - id: anObject [ - - id := anObject - ] - - nextId [ - - nextId ifNil: [nextId := Grease.GRPlatform current newRandom nextInt: 100000]. - nextId := nextId + 1. - ^nextId greaseString - ] - - applications [ - - ^applications ifNil: [applications := IdentityDictionary new] - ] - - dirtyWidgets [ - - ^self previousStateRegistry - ifNil: [#()] - ifNotNil: [self previousStateRegistry dirtyWidgets] - ] - - encoding [ - - ^self charset - ] - - route [ - - ^self context route - ] - - stateRegistry [ - - ^self context stateRegistry - ] - - previousStateRegistry [ - - ^self context previousStateRegistry - ] - - stateRegistry [ - - ^self context stateRegistry - ] - - previousStateRegistry [ - - ^self context previousStateRegistry - ] - - sessionManager [ - - ^ILSessionManager current - ] - - charset [ - - ^self preferenceAt: #charset ifAbsentPut: ['utf-8'] - ] - - charset: aString [ - - ^self preferenceAt: #charset put: aString - ] - - expirySeconds [ - - ^self preferenceAt: #expirySeconds ifAbsentPut: [self defaultExpirySeconds] - ] - - expirySeconds: anInteger [ - - ^self preferenceAt: #expirySeconds put: anInteger - ] - - language [ - - ^self preferenceAt: #language ifAbsentPut: [self defaultLanguage] - ] - - language: aSymbol [ - - ^self preferences at: #language put: aSymbol - ] - - refreshOnBacktrack [ - - ^self preferenceAt: #refreshOnBacktrack ifAbsentPut: [true] - ] - - refreshOnBacktrack: aBoolean [ - - ^self preferenceAt: #refreshOnBacktrack put: aBoolean - ] - - useCookies [ - - ^self preferenceAt: #cookies ifAbsentPut: [^true] - ] - - useCookies: aBoolean [ - - ^self preferenceAt: #cookies put: aBoolean - ] - - preferenceAt: aSymbol [ - - ^self preferences at: aSymbol ifAbsent: [nil] - ] - - preferenceAt: aSymbol ifAbsentPut: aBlock [ - - ^self preferences at: aSymbol ifAbsentPut: aBlock - ] - - preferenceAt: aSymbol put: anObject [ - - ^self preferences at: aSymbol put: anObject - ] - - preferences [ - - ^preferences ifNil: [preferences := Dictionary new] - ] - - createdTimestamp [ - - ^self timestamps at: #created ifAbsent: [self setCreatedTimestamp] - ] - - modifiedTimestamp [ - - ^self timestamps at: #modified ifAbsent: [self createdTimestamp] - ] - - setCreatedTimestamp [ - - self timestampAt: #created put: DateTime now - ] - - setModifiedTimestamp [ - - self timestampAt: #modified put: DateTime now - ] - - timestampAt: aSymbol [ - - ^self timestamps at: aSymbol ifAbsent: [nil] - ] - - timestampAt: aSymbol ifAbsentPut: aBlock [ - - ^self timestamps at: aSymbol ifAbsentPut: aBlock - ] - - timestampAt: aSymbol put: anObject [ - - ^self timestamps at: aSymbol put: anObject - ] - - timestamps [ - - ^timestamps ifNil: [timestamps := Dictionary new] - ] - - others [ - - ^others ifNil: [others := Dictionary new] - ] - - otherAt: aKey [ - - ^self others at: aKey ifAbsent: [nil] - ] - - otherAt: aKey put: anObject [ - - self others at: aKey put: anObject - ] - - otherAt: aKey ifAbsentPut: aBlock [ - - ^self others at: aKey ifAbsentPut: aBlock - ] - - defaultExpirySeconds [ - - ^1800 - ] - - defaultLanguage [ - - ^'en' - ] - - onExpire [ - - self redirect - ] - - stateRegistries [ - - ^stateRegistries ifNil: [stateRegistries := OrderedCollection new] - ] - - stateRegistryAt: aString [ - - ^self stateRegistries - detect: [:each | each key = aString] - ifNone: [nil] - ] - - newStateRegistry [ - - | registry | - registry := ILStateRegistry new. - self stateRegistries add: registry. - ^registry - ] - - actionRegistry [ - - ^actionRegistry ifNil: [ - actionRegistry := ILActionRegistry new] - ] - - actionAt: aKeyString [ - - ^self actionRegistry actionAt: aKeyString - ] - - actionFor: aBlock [ - - ^ILAction new - block: aBlock; - key: self nextId; - yourself - ] - - registerActionFor: aBlock [ - - | action | - action := self actionFor: aBlock. - self registerAction: action. - ^action - ] - - registerAction: anAction [ - - self actionRegistry register: anAction - ] - - evaluateActionKey: aString [ - - self actionRegistry evaluateActionKey: aString - ] - - redirect [ - - ILRedirectHandler new - produceResponse - ] - - redirectTo: anUrlString [ - - self context application redirectTo: anUrlString - ] - - redirectToLocal: anUrlString [ - - self context application redirectToLocal: anUrlString - ] - - redirectUrl [ - - ^redirectUrl - ] - - redirectUrl: aString [ - - redirectUrl := (self context urlBuilder urlForRedirection: aString) asString - ] - - redirectToIndex [ - - self context application redirectToIndex - ] - - isExpired [ - - (DateTime now asSeconds - self modifiedTimestamp asSeconds - > self expirySeconds) ifTrue: [ - self expire]. - ^expired - ] - - shouldUseSessionField [ - - ^(self request cookies - includesKey: self sessionManager cookieName) not - ] - - expire [ - - self actionRegistry unregisterAllActions. - expired := true - ] - - setRandomId [ - - ^self id: ILId new - ] -] diff --git a/iliad-stable/Core/Sessions/ILSessionManager.st b/iliad-stable/Core/Sessions/ILSessionManager.st deleted file mode 100644 index 03a1c00..0000000 --- a/iliad-stable/Core/Sessions/ILSessionManager.st +++ /dev/null @@ -1,219 +0,0 @@ -"====================================================================== -| -| Iliad.ILSessionManager class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILObject subclass: ILSessionManager [ - | sessions preferences | - - protocol. - -In addition, do not try to access the current session from here, -use ILContext>>session instead. - --- maintenance -- - -To remove all sessions, even not expired ones, call #removeAllSessions. -To remove all expired sessions, call #removeExpiredSessions'> - - ILSessionManager class [ - | current | - ] - - ILSessionManager class >> current [ - - ^current ifNil: [current := super new] - ] - - ILSessionManager class >> new [ - - self shouldNotImplement - ] - - sessions [ - - ^sessions values - ] - - expiredSessions [ - - ^sessions values select: [:each | each isExpired] - ] - - cookieName [ - - ^self preferenceAt: #cookieName ifAbsentPut: ['_iliad685744'] - ] - - cookieName: aString [ - - ^self preferenceAt: #cookieName put: aString - ] - - preferenceAt: aSymbol [ - - ^self preferences at: aSymbol ifAbsent: [nil] - ] - - preferenceAt: aSymbol ifAbsentPut: aBlock [ - - ^self preferences at: aSymbol ifAbsentPut: aBlock - ] - - preferenceAt: aSymbol put: anObject [ - - ^self preferences at: aSymbol put: anObject - ] - - preferences [ - - ^preferences ifNil: [preferences := Dictionary new] - ] - - sessionClass [ - - ^self preferenceAt: #sessionClass ifAbsentPut: [ILSession] - ] - - sessionClass: aSessionClass [ - - ^self preferences at: #sessionClass put: aSessionClass - ] - - addSession: aSession [ - - sessions at: aSession id greaseString put: aSession - ] - - sessionFor: aRequest [ - "Answer the according session for . - the session id may be found from cookies or fields. - If no session is found, create and return a new one" - - - - self shouldRemoveExpiredSessions ifTrue: [ - self removeExpiredSessions]. - ^self findOrMakeSessionFor: aRequest - ] - - sessionsDo: aBlock [ - - sessions values do: aBlock - ] - - initialize [ - - super initialize. - sessions := Dictionary new - ] - - shouldRemoveExpiredSessions [ - "Do not remove all expired sessions for each request" - - - ^(Grease.GRPlatform current newRandom nextInt: 10) = 10 - ] - - hasSession: aSession [ - - ^sessions values includes: aSession - ] - - findOrMakeSessionFor: aRequest [ - "Answer a valid session for . - Create a new session if no session is found" - - - | session id | - id := self sessionIdFromRequest: aRequest. - session := sessions at: id ifAbsent: [^self newSession]. - session isExpired - ifFalse: [ - session setModifiedTimestamp. - ^session] - ifTrue: [ - self removeSession: session. - ^session] - ] - - newSession [ - - | session | - session := self sessionClass new. - self addSession: session. - ^session - ] - - removeSession: aSession [ - - sessions - removeKey: aSession id greaseString - ifAbsent: [] - ] - - removeAllSessions [ - "Remove all sessions. Use for maintenance" - - - sessions := Dictionary new - ] - - removeExpiredSessions [ - "Remove all expired sessions" - - - self expiredSessions do: [:each | - self removeSession: each] - ] - - sessionIdFromCookies: cookies [ - - cookies ifNil: [^nil]. - ^cookies at: self cookieName ifAbsent: [nil] - ] - - sessionIdFromRequest: aRequest [ - - ^aRequest sessionField ifNil: [ - self sessionIdFromCookies: aRequest cookies] - ] -] diff --git a/iliad-stable/Core/Sessions/ILStateRegistry.st b/iliad-stable/Core/Sessions/ILStateRegistry.st deleted file mode 100644 index 8b5c699..0000000 --- a/iliad-stable/Core/Sessions/ILStateRegistry.st +++ /dev/null @@ -1,116 +0,0 @@ -"====================================================================== -| -| Iliad.ILStateRegistry class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - -ILObject subclass: ILStateRegistry [ - | key states | - - - - - ILStateRegistry class >> fromRegistry: aStateRegistry [ - - ^self new - setStates: aStateRegistry states copy; - yourself - ] - - key [ - - ^key ifNil: [key := self session nextId] - ] - - stateAt: aWidget [ - - ^self states - at: aWidget - ifAbsent: [aWidget state] - ] - - states [ - - ^states ifNil: [states := Dictionary new] - ] - - setStates: aDictionary [ - - states := aDictionary - ] - - widgets [ - - ^self states keys - ] - - register: aWidget [ - - self states at: aWidget put: aWidget state - ] - - unregister: aWidget [ - - self states - removeKey: aWidget - ifAbsent: [nil] - ] - - unregisterAllWidgets [ - - states := nil - ] - - dirtyWidgets [ - "Answer all widgets which state has changed" - - ^self dirtyChildrenOf: self session application - ] - - dirtyChildrenOf: aBuildable [ - - | dirtyWidgets | - dirtyWidgets := OrderedCollection new. - aBuildable children do: [:each | - (self isWidgetDirty: each) - ifTrue: [dirtyWidgets add: each] - ifFalse: [dirtyWidgets addAll: (self dirtyChildrenOf: each)]]. - ^dirtyWidgets - ] - - isWidgetDirty: aWidget [ - - ^(self stateAt: aWidget) ~= aWidget state - ] -] diff --git a/iliad-stable/Core/Sessions/ILUrlBuilder.st b/iliad-stable/Core/Sessions/ILUrlBuilder.st deleted file mode 100644 index 079706e..0000000 --- a/iliad-stable/Core/Sessions/ILUrlBuilder.st +++ /dev/null @@ -1,205 +0,0 @@ -"====================================================================== -| -| Iliad.ILUrlBuilder class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2010 -| Nicolas Petton , -| Sébastien Audier -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - -ILObject subclass: ILUrlBuilder [ - | baseUrl | - - - - - ILUrlBuilder class [ - | actionKey hashKey sessionKey ajaxUploadKey stateKey rewriteRules | - - rewriteRules [ - "Rewrite rules are used to replace patterns in the baseUrl" - - - ^rewriteRules ifNil: [rewriteRules := OrderedCollection new] - ] - - addRewriteRule: aBlock [ - - self rewriteRules add: aBlock - ] - - actionKey [ - - ^actionKey ifNil: [actionKey := self defaultActionKey] - ] - - hashKey [ - - ^hashKey ifNil: [hashKey := self defaultHashKey] - ] - - sessionKey [ - - ^sessionKey ifNil: [sessionKey := self defaultSessionKey] - ] - - ajaxUploadKey [ - - ^ajaxUploadKey ifNil: [ajaxUploadKey := self defaultAjaxUploadKey] - ] - - stateKey [ - - ^stateKey ifNil: [stateKey := self defaultStateKey] - ] - - defaultActionKey [ - - ^'_action' - ] - - defaultHashKey [ - - ^'_hash' - ] - - defaultSessionKey [ - - ^'_session' - ] - - defaultAjaxUploadKey [ - - ^'_ajax_upload' - ] - - defaultStateKey [ - - ^'_state' - ] - ] - - actionKey [ - - ^self class actionKey - ] - - hashKey [ - - ^self class hashKey - ] - - sessionKey [ - - ^self class sessionKey - ] - - stateKey [ - - ^self class stateKey - ] - - rewriteRules [ - - ^self class rewriteRules - ] - - addDefaultParametersTo: anUrl [ - - self shouldUseSessionField ifTrue: [ - anUrl - addParameter: self sessionKey - value: self session id greaseString] - ] - - baseUrl [ - - baseUrl ifNil: [self buildBaseUrl]. - ^baseUrl copy - ] - - urlFor: aString [ - - | url | - url := ILUrl absolute: aString. - self addDefaultParametersTo: url. - ^self applyRewriteRulesTo: url - ] - - urlForAction: anAction [ - - ^self urlForAction: anAction hash: '' - ] - - urlForAction: anAction hash: aHashString [ - - ^self urlForActionKey: anAction key hash: aHashString - ] - - urlForActionKey: aKeyString hash: aHashString [ - - | url | - url := self baseUrl. - url - addParameter: self actionKey value: aKeyString; - addParameter: self stateKey value: self session stateRegistry key. - aHashString notEmpty ifTrue: [ - url addParameter: self hashKey value: aHashString]. - ^url - ] - - urlForRedirection: aString [ - - ^ILUrl absolute: aString - ] - - applyRewriteRulesTo: anUrl [ - - | tempUrl | - tempUrl := anUrl. - self rewriteRules do: [:each | - tempUrl := ILUrl absolute: (each value: tempUrl greaseString)]. - ^tempUrl - ] - - shouldUseSessionField [ - - ^(self request cookies - includesKey: self session sessionManager cookieName) not - ] - - buildBaseUrl [ - - baseUrl:= self context request url copy. - {self stateKey. self actionKey} do: [:each | - baseUrl removeParameter: each]. - self application updateBaseUrl: baseUrl - ] -] diff --git a/iliad-stable/Core/Utilities/ILComposite.st b/iliad-stable/Core/Utilities/ILComposite.st deleted file mode 100644 index e5acf83..0000000 --- a/iliad-stable/Core/Utilities/ILComposite.st +++ /dev/null @@ -1,101 +0,0 @@ -"====================================================================== -| -| Iliad.ILComposite class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2010 -| Nicolas Petton , -| Sébastien Audier -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - -ILObject subclass: ILComposite [ - | tail next | - - - - - = anObject [ - - ^self species = anObject species and: [ - self children = anObject children] - ] - - hash [ - - ^self species hash bitXor: self children hash - ] - - children [ - - | children | - children := OrderedCollection new. - self childrenDo: [:each | - children add: each]. - ^children - ] - - next [ - - ^next - ] - - next: aComposite [ - - next := aComposite - ] - - add: aComposite [ - - | head | - tail ifNil: [tail := aComposite]. - head := tail next ifNil: [tail]. - tail next: aComposite. - tail := tail next. - tail next: head. - ^aComposite - ] - - allChildrenDo: aBlock [ - - self childrenDo: [:each | - aBlock value: each. - each allChildrenDo: aBlock] - ] - - childrenDo: aBlock [ - - | child | - tail ifNil: [^self]. - child := tail next. - [child == tail] whileFalse: [ - aBlock value: child. - child := child next]. - aBlock value: tail - ] -] diff --git a/iliad-stable/Core/Utilities/ILDynamicVariable.st b/iliad-stable/Core/Utilities/ILDynamicVariable.st deleted file mode 100644 index fab56c5..0000000 --- a/iliad-stable/Core/Utilities/ILDynamicVariable.st +++ /dev/null @@ -1,75 +0,0 @@ -"====================================================================== -| -| Iliad.ILDynamicVariable class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -Object subclass: ILDynamicVariable [ - - - - ILDynamicVariable class [ - | processVariable | - - defaultValue [ - - ^nil - ] - - use: anObject during: aBlock [ - - ^self processVariable use: anObject during: aBlock - ] - - value [ - - ^self processVariable value - ] - - processVariable [ - ^processVariable ifNil: [ - processVariable := ProcessEnvironment uniqueInstance associationAt: self] - ] - ] -] - -ProcessVariable extend [ - use: anObject during: aBlock [ - | oldValue | - oldValue := self value. - self value: anObject. - ^aBlock ensure: [self value: oldValue] - ] -] diff --git a/iliad-stable/Core/Utilities/ILEncoder.st b/iliad-stable/Core/Utilities/ILEncoder.st deleted file mode 100644 index 18e784a..0000000 --- a/iliad-stable/Core/Utilities/ILEncoder.st +++ /dev/null @@ -1,46 +0,0 @@ -Object subclass: ILEncoder [ - - - - - ILEncoder class [ - - printUrl: aString encoded: aBoolean on: aStream [ - - aBoolean - ifTrue: [self encodeUrl: aString on: aStream] - ifFalse: [aStream nextPutAll: aString] - ] - - encodeUrl: aString on: aStream[ - - aString do: [:char | - self encodeUrlCharacter: char on: aStream] - ] - - encodeUrlCharacter: aCharacter on: aStream [ - - | value | - ('ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789-_."' includes: aCharacter) - ifTrue: [^aStream nextPut: aCharacter]. - value := aCharacter asInteger. - aStream nextPut: $%. - aStream nextPutAll: ((value radix: 16) copyFrom: 4) - ] - - encodeForHTTP: aString on: aStream [ - - aString do: [:char | - self encodeCharacterForHTTP: char on: aStream] - ] - - encodeCharacterForHTTP: aCharacter on: aStream [ - - aCharacter = $" ifTrue: [^aStream nextPutAll: '"']. - aCharacter = $< ifTrue: [^aStream nextPutAll: '<']. - aCharacter = $& ifTrue: [^aStream nextPutAll: '&']. - aCharacter = $> ifTrue: [^aStream nextPutAll: '>']. - aStream nextPut: aCharacter - ] - ] -] diff --git a/iliad-stable/Core/Utilities/ILId.st b/iliad-stable/Core/Utilities/ILId.st deleted file mode 100644 index 86af54f..0000000 --- a/iliad-stable/Core/Utilities/ILId.st +++ /dev/null @@ -1,53 +0,0 @@ -ByteArray subclass: ILId [ - - - - - - ILId class >> defaultSize [ - - ^12 - ] - - ILId class >> new [ - - ^self new: self defaultSize - ] - - ILId class >> new: anInteger [ - - ^(self basicNew: anInteger) - initialize; - yourself - ] - - initialize [ - - Grease.GRPlatform current semaphoreClass forMutualExclusion critical: [ - self at: 1 put: ($a to: $z) atRandom asInteger. - 2 to: self size do: [:each | - self at: each put: self table atRandom asInteger]] - ] - - table [ - - ^($a to: $z), ($A to: $Z), ($0 to: $9), (Array with: $_ with: $-) - ] - - printOn: aStream [ - - self do: [:each | - aStream nextPut: (Character value: each)] - ] -] - - - -Character extend [ - - to: aCharacter [ - ^self codePoint - to: aCharacter codePoint - collect: [:i | Character codePoint: i] - ] -] diff --git a/iliad-stable/Core/Utilities/ILModelProxy.st b/iliad-stable/Core/Utilities/ILModelProxy.st deleted file mode 100644 index 7e0eb12..0000000 --- a/iliad-stable/Core/Utilities/ILModelProxy.st +++ /dev/null @@ -1,110 +0,0 @@ -"====================================================================== -| -| Iliad.ILModelProxy class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Some parts of this file reuse code from the Seaside framework written -| by Avi Bryant, Julian Fitzell, Lukas Renggli, Michel Bany, Philippe -| Marschall and Seaside contributors http://www.seaside.st -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -Object subclass: ILModelProxy [ - | cache model | - - - - - ILModelProxy class >> on: anObject [ - - ^self new setModel: anObject - ] - - commit [ - - cache - keysAndValuesDo: [:key :value | self performRealWrite: key with: value]. - cache := Dictionary new - ] - - doesNotUnderstand: aMessage [ - - ^aMessage selector isUnary - ifTrue: [self performRead: aMessage selector] - ifFalse: - [(aMessage selector isKeyword and: [aMessage arguments size = 1]) - ifTrue: [ - self performWrite: aMessage selector allButLast with: aMessage argument] - ifFalse: [super doesNotUnderstand: aMessage]] - ] - - model [ - - ^model - ] - - performRead: aSymbol [ - - ^cache at: aSymbol asSymbol ifAbsent: [model perform: aSymbol] - ] - - performRealWrite: aSymbol with: anObject [ - - model perform: (aSymbol copyWith: $:) asSymbol with: anObject - ] - - performWrite: aSymbol with: anObject [ - - cache at: aSymbol asSymbol put: anObject - ] - - setModel: anObject [ - - model := anObject. - cache := Dictionary new - ] -] - - -Symbol extend [ - - isKeyword [ - - ^self last = $: - ] - - isUnary [ - - ^self numArgs = 0 - ] -] diff --git a/iliad-stable/Core/Utilities/ILObject.st b/iliad-stable/Core/Utilities/ILObject.st deleted file mode 100644 index 18add98..0000000 --- a/iliad-stable/Core/Utilities/ILObject.st +++ /dev/null @@ -1,67 +0,0 @@ -"====================================================================== -| -| Iliad.ILObject class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -Grease.GRObject subclass: ILObject [ - - - - - application [ - - ^self context application - ] - - context [ - - ^ILCurrentContext value - ] - - urlBuilder [ - - ^self context urlBuilder - ] - - session [ - - ^self context session - ] - - request [ - - ^self context request - ] -] diff --git a/iliad-stable/Core/lib/HTTP/ILCookie.st b/iliad-stable/Core/lib/HTTP/ILCookie.st deleted file mode 100644 index 91f1c1c..0000000 --- a/iliad-stable/Core/lib/HTTP/ILCookie.st +++ /dev/null @@ -1,152 +0,0 @@ -"====================================================================== -| -| Iliad.ILCookie class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Adapted from the WACookie class of Seaside 2.8. -| The Seaside framework is written by Avi Bryant, Julian Fitzell, -| Lukas Renggli, Michel Bany, Philippe Marschall and Seaside contributors -| http://www.seaside.st -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -Object subclass: ILCookie [ - | expiry key path value | - - - - - ILCookie class >> key: keyString value: valueString [ - - ^(self new) - key: keyString; - value: valueString; - yourself - ] - - expiryString [ - - self expiry ifNil: [^'']. - ^(Grease.GRPrinter rfc822WithTimeZone: 'GMT') print: (DateTime fromSeconds: self expiry) - ] - - writeOn: aStream [ - - aStream - nextPutAll: self key; - nextPut: $=; - nextPutAll: (self value ifNil: ['']). - expiry isNil - ifFalse: - [aStream - nextPutAll: '; expires='; - nextPutAll: self expiryString]. - path isNil - ifFalse: - [aStream - nextPutAll: '; path='; - nextPutAll: self path] - ] - - = other [ - - ^self species = other species - and: [self key = other key and: [self path = other path]] - ] - - hash [ - - ^self key hash bitXor: self path hash - ] - - expireIn: aDuration [ - - self - expiry: ((DateTime fromSeconds: DateTime now asSeconds) asSeconds - + aDuration asSeconds) - ] - - valueWithExpiry [ - - ^expiry ifNil: [self value] - ifNotNil: [(self value ifNil: ['']) , '; expires=' , self expiryString] - ] - - expiry [ - - ^expiry - ] - - expiry: anInteger [ - - expiry := anInteger - ] - - key [ - - ^key - ] - - key: aString [ - - key := aString - ] - - path [ - - ^path ifNil: ['/'] - ] - - path: aString [ - - path := aString - ] - - value [ - - ^value - ] - - value: aString [ - - value := aString - ] -] - diff --git a/iliad-stable/Core/lib/HTTP/ILFileProxy.st b/iliad-stable/Core/lib/HTTP/ILFileProxy.st deleted file mode 100644 index 9283a11..0000000 --- a/iliad-stable/Core/lib/HTTP/ILFileProxy.st +++ /dev/null @@ -1,120 +0,0 @@ -"====================================================================== -| -| Iliad.ILFileProxy class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -Object subclass: ILFileProxy [ - | filename contentType contents timestamps | - - - - ILFileProxy class >> new [ - - ^self basicNew - initialize; - yourself - ] - - initialize [ - - self setCreatedTimestamp - ] - - setCreatedTimestamp [ - - self timestampsAt: #created put: DateTime now - ] - - contentType [ - - ^contentType - ] - - contentType: anObject [ - - contentType := anObject - ] - - contents [ - - ^contents - ] - - contents: anObject [ - - contents := anObject - ] - - createdTimestamp [ - - ^self timestampsAt: #created - ] - - filename [ - - ^filename - ] - - filename: anObject [ - - filename := anObject - ] - - timestamps [ - - ^timestamps ifNil: [timestamps := Dictionary new] - ] - - timestampsAt: aSymbol [ - - ^self timestamps at: aSymbol ifAbsent: [nil] - ] - - timestampsAt: aSymbol put: aTimestamp [ - - ^self timestamps at: aSymbol put: aTimestamp - ] - - writeToFile [ - - | file | - file := File name: self filename. - (file writeStream) - nextPutAll: self contents; - close - ] -] - diff --git a/iliad-stable/Core/lib/HTTP/ILRequest.st b/iliad-stable/Core/lib/HTTP/ILRequest.st deleted file mode 100644 index a0a9efd..0000000 --- a/iliad-stable/Core/lib/HTTP/ILRequest.st +++ /dev/null @@ -1,262 +0,0 @@ -"====================================================================== -| -| Iliad.ILRequest class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Adapted from the WARequest class of Seaside 2.8. -| The Seaside framework is written by Avi Bryant, Julian Fitzell, -| Lukas Renggli, Michel Bany, Philippe Marschall and Seaside contributors -| http://www.seaside.st -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -Object subclass: ILRequest [ - | url fields headers cookies method nativeRequest | - - - - ILRequest class >> new [ - - ^self basicNew - initialize; - yourself - ] - - initialize [ - - headers := Dictionary new. - fields := Dictionary new. - cookies := Dictionary new - ] - - at: key [ - - ^fields at: key - ] - - at: key ifAbsent: aBlock [ - - ^fields at: key ifAbsent: aBlock - ] - - cookies [ - - ^cookies - ] - - cookies: anObject [ - - cookies := anObject - ] - - fields [ - - ^fields - ] - - fields: anObject [ - - fields := anObject - ] - - hashLocationField [ - - ^self - at: ILUrlBuilder hashKey - ifAbsent: [nil] - ] - - sessionField [ - - ^self - at: ILUrlBuilder sessionKey - ifAbsent: [nil] - ] - - actionField [ - - ^self - at: ILUrlBuilder actionKey - ifAbsent: [nil] - ] - - ajaxUploadField [ - - ^self - at: ILUrlBuilder ajaxUploadKey - ifAbsent: [nil] - ] - - jsonField [ - - ^self - at: ILUrlBuilder jsonKey - ifAbsent: [nil] - ] - - stateField [ - - ^self - at: ILUrlBuilder stateKey - ifAbsent: [nil] - ] - - headerAt: aKey [ - - ^self headerAt: aKey ifAbsent: [] - ] - - headerAt: aKey ifAbsent: aBlock [ - - ^headers at: aKey ifAbsent: aBlock - ] - - headers [ - - ^headers - ] - - headers: aDictionary [ - - headers := aDictionary - ] - - method [ - - ^method - ] - - method: aString [ - - method := aString - ] - - nativeRequest [ - - ^nativeRequest - ] - - nativeRequest: aRequest [ - - nativeRequest := aRequest - ] - - password [ - - ^self authorization ifNotNilDo: [:auth | auth copyAfter: $:] - ] - - url [ - - ^url - ] - - url: anUrl [ - - url := anUrl - ] - - user [ - - ^self authorization ifNotNilDo: [:auth | auth copyUpTo: $:] - ] - - userAgent [ - - ^self headerAt: 'user-agent' - ] - - hasCookies [ - - ^self cookies notNil and: [self cookies notEmpty] - ] - - isAjaxRequest [ - - ^(self headerAt: 'x-requested-with') = 'XMLHttpRequest' - ] - - isGet [ - - ^self method asUppercase = 'GET' - ] - - isPost [ - - ^self method asUppercase = 'POST' - ] - - isPrefetch [ - - ^(self headerAt: 'HTTP_X_MOZ') = 'prefetch' - ] - - isPut [ - - ^self method asUppercase = 'PUT' - ] - - isTypeOfRequestForRedirect [ - - ^self isPost or: [ - self actionField notNil] - ] - - isTypeOfRequestForJson [ - - ^(self headerAt: 'accept' ifAbsent: ['']) matchRegex: '.*application/json.*' - ] - - authorization [ - - ^(self headerAt: 'Authorization' ifAbsent: [self headerAt: 'authorization']) - ifNotNilDo: [:auth | self decodeAuthorization: auth] - ] - - decodeAuthorization: aString [ - - ^Grease.GRPlatform current base64Decode: (aString tokenize: ' ') last - ] - - setMethod: methodString url: urlString headers: headDict fields: fieldDict cookies: cookieDict [ - - method := methodString. - url := urlString. - headers := headDict. - fields := fieldDict. - cookies := cookieDict - ] -] - diff --git a/iliad-stable/Core/lib/HTTP/ILResponse.st b/iliad-stable/Core/lib/HTTP/ILResponse.st deleted file mode 100644 index e8a3398..0000000 --- a/iliad-stable/Core/lib/HTTP/ILResponse.st +++ /dev/null @@ -1,225 +0,0 @@ -"====================================================================== -| -| Iliad.ILResponse class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Adapted from the WAResponse class of Seaside 2.8. -| The Seaside framework is written by Avi Bryant, Julian Fitzell, -| Lukas Renggli, Michel Bany, Philippe Marschall and Seaside contributors -| http://www.seaside.st -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -Object subclass: ILResponse [ - | contentType headers cookies status stream | - - - - ILResponse class >> new [ - - ^self basicNew - initialize; - yourself - ] - - ILResponse class >> forbidden [ - - ^self new forbidden - ] - - ILResponse class >> notFound [ - - ^self new notFound - ] - - ILResponse class >> ok [ - - ^self new ok - ] - - ILResponse class >> redirect [ - - ^self new redirect - ] - - addCookie: aCookie [ - - cookies ifNil: [cookies := Set new]. - cookies add: aCookie - ] - - contentType [ - - ^contentType - ] - - contentType: mimeTypeString [ - - contentType := mimeTypeString - ] - - contents [ - - ^stream contents - ] - - contents: aStream [ - - stream := aStream - ] - - cookieAt: key put: value [ - - ^self addCookie: (ILCookie key: key value: value) - ] - - cookies [ - - ^cookies ifNil: [#()] - ] - - headerAt: key put: value [ - - headers ifNil: [headers := OrderedCollection new]. - headers add: (Association key: key value: value) - ] - - headers [ - - ^headers ifNil: [#()] - ] - - initialize [ - - stream := WriteStream on: String new. - status := '200'. - contentType := 'text/html; charset=utf-8' - ] - - nextPut: aCharacter [ - - stream nextPut: aCharacter asCharacter - ] - - nextPutAll: aString [ - - aString do: [:ea | self nextPut: ea] - ] - - space [ - - stream space - ] - - release [ - - stream := cookies := headers := nil - ] - - status [ - - ^status - ] - - status: anInteger [ - - status := anInteger - ] - - stream [ - - ^stream - ] - - stream: aStream [ - - stream := aStream - ] - - attachmentWithFileName: aString [ - - self headerAt: 'Content-dispostion' - put: 'attachment; filename="' , aString , '"' - ] - - basicAuthenticationRealm: aString [ - - self headerAt: 'WWW-Authenticate' put: 'Basic realm="' , aString , '"'. - self authenticationFailed - ] - - redirectTo: aString [ - - self headerAt: 'Location' put: aString. - self redirect - ] - - authenticationFailed [ - - self status: 401 - ] - - forbidden [ - - self status: 403 - ] - - internalError [ - - self status: 500 - ] - - notFound [ - - self status: 404 - ] - - ok [ - - self status: 200 - ] - - redirect [ - - self status: 302 - ] - - printOn: aStream [ - - super printOn: aStream. - aStream space; nextPutAll: self status greaseString - ] -] - diff --git a/iliad-stable/Core/lib/HTTP/ILUrl.st b/iliad-stable/Core/lib/HTTP/ILUrl.st deleted file mode 100644 index a729296..0000000 --- a/iliad-stable/Core/lib/HTTP/ILUrl.st +++ /dev/null @@ -1,509 +0,0 @@ -"====================================================================== -| -| Iliad.ILUrl class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Adapted from the WAUrl class of Seaside 2.8. -| The Seaside framework is written by Avi Bryant, Julian Fitzell, -| Lukas Renggli, Michel Bany, Philippe Marschall and Seaside contributors -| http://www.seaside.st -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - - -Object subclass: ILUrl [ - | scheme username password hostname port path parameters fragment | - - - or nil -username: or nil -password: or nil -hostname: or nil -port: or nil -path: or nil -parameters: -fragment: or nil'> - - ILUrl class >> absolute: aString [ - "Parse aString as an absolute URL." - - - ^self basicNew initializeFromString: aString - ] - - ILUrl class >> absolute: aString relative: aRelativeString [ - "Take absolute URL aString and combine it with a relative path aRelativeString." - - - ^(self absolute: aString) - parsePath: aRelativeString; - yourself - ] - - ILUrl class >> decodePercent: aString [ - "percent decodes the given String" - - - | input output char | - input := aString readStream. - output := WriteStream on: (String new: aString size). - [input atEnd] whileFalse: - [char := input next. - output nextPut: (char = $+ - ifTrue: [Character space] - ifFalse: [char = $% - ifTrue: [ - Character value: input next asUppercase digitValue * 16 - + input next asUppercase digitValue] - ifFalse: [char]])]. - ^output contents - ] - - ILUrl class >> new [ - - ^self basicNew initialize - ] - - = anUrl [ - - ^self class = anUrl class and: [self greaseString = anUrl greaseString] - ] - - hash [ - - ^self hostname hash bitXor: self path hash - ] - - , aString [ - - ^self greaseString, aString greaseString - ] - - addAllToPath: aCollectionOfStrings [ - "convenice method to add a collection of strings to the path" - - - aCollectionOfStrings do: [:each | self addToPath: each] - ] - - addParameter: aString [ - - self addParameter: aString value: nil - ] - - addParameter: keyString value: valueString [ - - self parameters at: keyString put: valueString - ] - - addToPath: aString [ - - self path addAll: (aString tokenize: '/') - ] - - removeParameter: aString [ - - self parameters removeKey: aString ifAbsent: [] - ] - - greaseString [ - - ^self asString - ] - - asString [ - - ^self printString - ] - - pathString [ - "Answer the path converted to a string." - - - ^String streamContents: [:stream | self printPathOn: stream encoded: false] - ] - - relativeTo: anUrl [ - "Answer a path element collection relative from the receiver to anUrl." - - - | currentPath argumentPath resultingPath | - currentPath := self path copy. - argumentPath := anUrl path copy. - - [currentPath notEmpty - and: [argumentPath notEmpty and: [currentPath first = argumentPath first]]] - whileTrue: - [currentPath removeFirst. - argumentPath removeFirst]. - resultingPath := OrderedCollection new. - currentPath size timesRepeat: [resultingPath add: '..']. - resultingPath addAll: argumentPath. - ^resultingPath - ] - - decode: aString [ - "percent decodes the given String" - - - ^self class decodePercent: aString - ] - - removeParameters [ - - parameters := nil - ] - - takeServerParametersFromRequest: aRequest [ - - | httpHost | - hostname ifNil: - [httpHost := aRequest headerAt: 'host' ifAbsent: [^self]. - hostname := httpHost copyUpTo: $:. - (httpHost includes: $:) - ifTrue: [port := (httpHost copyAfter: $:) asNumber]] - ] - - printOn: aStream encoded: aBoolean usingHtmlEntities: anotherBoolean [ - - self printServerOn: aStream encoded: aBoolean. - self printPathOn: aStream encoded: aBoolean. - self printParametersOn: aStream encoded: aBoolean usingHtmlEntities: anotherBoolean. - self printFragmentOn: aStream encoded: aBoolean - ] - - printParametersOn: aStream encoded: aBoolean usingHtmlEntities: anotherBoolean [ - - | first | - first := true. - parameters ifNil: [^self]. - parameters keysAndValuesDo: [:key :value | - aStream nextPutAll: (first - ifTrue: [first := false. '?'] - ifFalse: [anotherBoolean ifTrue: ['&'] ifFalse: ['&']]). - ILEncoder printUrl: key encoded: aBoolean on: aStream. - value ifNotNil: [ - aStream nextPut: $=. - ILEncoder printUrl: value greaseString encoded: aBoolean on: aStream]] - ] - - printPathOn: aStream encoded: aBoolean [ - - path ifNil: [^self]. - aStream nextPut: $/. - path - do: [:each | - ILEncoder printUrl: each encoded: aBoolean on: aStream] - separatedBy: [aStream nextPut: $/] - ] - - printServerOn: aStream encoded: aBoolean [ - - hostname ifNil: [^self]. - aStream - nextPutAll: scheme; - nextPutAll: '://'. - username notNil ifTrue: [ - ILEncoder printUrl: username encoded: aBoolean on: aStream. - password notNil ifTrue: [ - aStream nextPut: $:. - ILEncoder printUrl: password encoded: aBoolean on: aStream]. - aStream nextPut: $@]. - ILEncoder printUrl: hostname encoded: aBoolean on: aStream. - port notNil ifTrue: [ - ((scheme = 'http' and: [port = 80]) - or: [scheme = 'https' and: [port = 443]]) - ifFalse: [ - aStream - nextPut: $:; - print: port]] - ] - - printFragmentOn: aStream encoded: aBoolean [ - - fragment ifNil: [^self]. - aStream nextPut: $#. - ILEncoder printUrl: fragment encoded: aBoolean on: aStream - ] - - fragment [ - "Answer the fragment part of the URL." - - - ^fragment - ] - - fragment: aString [ - - fragment := aString - ] - - hostname [ - "Answer the host part of the URL." - - - ^hostname - ] - - hostname: aString [ - - hostname := aString - ] - - parameters [ - - ^parameters ifNil: [parameters := Grease.GRSmallDictionary new] - ] - - password [ - "Answer the password part of the URL." - - - ^password - ] - - password: aString [ - - password := aString - ] - - path [ - "Answer the path part of the URL." - - - ^path ifNil: [path := OrderedCollection new] - ] - - path: aCollection [ - "Set the path part of the URL to aCollection." - - - path := aCollection - ] - - port [ - "Answer the port number part of the URL." - - - ^port - ] - - port: aNumber [ - - port := aNumber - ] - - scheme [ - "Answer the URL's scheme." - - - ^scheme - ] - - scheme: aString [ - "we really expect a String here, Old versions (2.7) expected a Symbol you can still pass a Symbol and get away with it but don't expect this behavior to be supported in future versions. - #greaseString is the 'correct' way to convert a Symbol to a String since #displayString will add a hash on VW" - - - scheme := aString greaseString - ] - - username [ - "Answer the username part of the URL." - - - ^username - ] - - username: aString [ - - username := aString - ] - - initialize [ - - scheme := 'http' - ] - - initializeFromString: aString [ - - | string index | - self initialize. - string := aString. - index := string indexOf: $#. - index > 0 - ifTrue: [ - self parseFragment: (string copyFrom: index + 1 to: string size). - string := string copyFrom: 1 to: index - 1]. - index := string indexOf: $?. - index > 0 - ifTrue: [ - self parseParameters: (string copyFrom: index + 1 to: string size). - string := string copyFrom: 1 to: index - 1]. - index := string indexOfSubCollection: '://'. - index > 0 - ifTrue: [ - self scheme: (string copyFrom: 1 to: index - 1). - string := string copyFrom: index + 3 to: string size. - index := string indexOf: $/. - string := index > 0 - ifFalse: [self parseHost: string. ''] - ifTrue: [ - self parseHost: (string copyFrom: 1 to: index - 1). - string copyFrom: index + 1 to: string size]]. - self parsePath: string - ] - - parseFragment: aString [ - - aString isEmpty ifTrue: [^self]. - self fragment: (self decode: aString) - ] - - parseHost: aString [ - - | string temp index | - aString isEmpty ifTrue: [^self]. - string := aString. - index := string indexOf: $@. - index > 1 - ifTrue: - [temp := string copyFrom: 1 to: index - 1. - string := string copyFrom: index + 1 to: string size. - index := temp indexOf: $:. - index > 0 - ifFalse: [self username: (self decode: temp)] - ifTrue: [ - self username: (self decode: (temp copyFrom: 1 to: index - 1)). - self password: (self decode: (temp copyFrom: index + 1 to: temp size))]]. - index := string indexOf: $:. - index > 0 - ifTrue: [ - temp := string copyFrom: index + 1 to: string size. - string := string copyFrom: 1 to: index - 1. - self - port: ((temp notEmpty and: [temp allSatisfy: [:each | each isDigit]]) - ifTrue: [temp asInteger])]. - self hostname: (self decode: string) - ] - - parseParameters: aString [ - - | input string index | - input := aString readStream. - [input atEnd] whileFalse: - [string := input upTo: $&. - index := string indexOf: $=. - index > 0 - ifFalse: [self addParameter: (self decode: string)] - ifTrue: [ - self addParameter: (self decode: (string copyFrom: 1 to: index - 1)) - value: (self decode: (string copyFrom: index + 1 to: string size))]] - ] - - parsePath: aString [ - - | input part | - input := aString readStream. - input peek = $/ ifTrue: [path := nil]. - [input atEnd] whileFalse: [ - part := input upTo: $/. - part isEmpty ifFalse: [ - part = '..' - ifTrue: [self path isEmpty ifFalse: [self path removeLast]] - ifFalse: [part = '.' ifFalse: [self path addLast: (self decode: part)]]]] - ] - - postCopy [ - - super postCopy. - scheme := scheme copy. - username := username copy. - password := password copy. - hostname := hostname copy. - port := port copy. - path := path copy. - parameters := parameters copy. - fragment := fragment copy - ] - - with: pathString [ - - ^self copy - addToPath: pathString; - yourself - ] - - withParameter: aString [ - - ^self copy - addParameter: aString; - yourself - ] - - withParameter: aString value: valueString [ - - ^self copy - addParameter: aString value: valueString; - yourself - ] - - withoutParameters [ - - ^self copy - removeParameters; - yourself - ] - - printOn: aStream encoded: aBoolean [ - - self printOn: aStream encoded: aBoolean usingHtmlEntities: false - ] - - printOn: aStream [ - - self printOn: aStream encoded: true - ] - - printEncodedOn: aStream [ - - self printOn: aStream encoded: false usingHtmlEntities: true - ] -] - diff --git a/iliad-stable/Core/lib/JSON/Extensions.st b/iliad-stable/Core/lib/JSON/Extensions.st deleted file mode 100644 index 61eb3ad..0000000 --- a/iliad-stable/Core/lib/JSON/Extensions.st +++ /dev/null @@ -1,130 +0,0 @@ -"====================================================================== -| -| Smalltalk class extensions -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Adapted from Displomacy written by Avi Bryant -| http://www.squeaksource.com/Diplomacy. -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -Number extend [ - - printJsonOn: aStream [ - - aStream nextPutAll: self greaseString - ] -] - -Collection extend [ - - printJsonOn: aStream [ - - | needComma | - needComma := false. - aStream nextPut: $[. - self do: [:v | - needComma - ifTrue: [ aStream nextPutAll: ', ' ] - ifFalse: [ needComma := true ]. - v printJsonOn: aStream]. - aStream nextPut: $]. - ] -] - -Dictionary extend [ - - printJsonOn: aStream [ - - | needComma | - needComma := false. - aStream nextPut: ${. - self keysAndValuesDo: [:k :v | - needComma - ifTrue: [ aStream nextPutAll: ', ' ] - ifFalse: [ needComma := true ]. - k greaseString printJsonOn: aStream. - aStream nextPutAll: ': '. - v printJsonOn: aStream]. - aStream nextPut: $}. - ] -] - - - -String extend [ - - printJsonOn: aStream [ - - | replacement | - aStream nextPut: $". - self do: [:ch | - replacement := Iliad.ILJson escapeForCharacter: ch. - replacement - ifNil: [ aStream nextPut: ch ] - ifNotNil: [ aStream nextPut: $\; nextPut: replacement ]]. - aStream nextPut: $". - ] -] - -True extend [ - - printJsonOn: aStream [ - - aStream nextPutAll: 'true' - ] -] - -False extend [ - - printJsonOn: aStream [ - - aStream nextPutAll: 'false' - ] -] - -UndefinedObject extend [ - - printJsonOn: aWriteStream [ - - aWriteStream nextPutAll: 'null' - ] -] - -WriteStream extend [ - - jsonPrint: anObject [ - - anObject printJsonOn: self - ] -] diff --git a/iliad-stable/Core/lib/JSON/ILJson.st b/iliad-stable/Core/lib/JSON/ILJson.st deleted file mode 100644 index dc93269..0000000 --- a/iliad-stable/Core/lib/JSON/ILJson.st +++ /dev/null @@ -1,344 +0,0 @@ -"====================================================================== -| -| Iliad.ILJson class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Adapted from Displomacy written by Avi Bryant -| http://www.squeaksource.com/Diplomacy. -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILObject subclass: ILJson [ - | stream ctorMap | - - - - - CharacterEscapeMap := nil. - - ILJson class >> escapeForCharacter: c [ - ^CharacterEscapeMap at: c ifAbsent: [nil] - ] - - ILJson class >> initialize [ - "ILJson initialize." - - CharacterEscapeMap := Dictionary new - at: $" put: $"; - at: $\ put: $\; - at: Character backspace put: $b; - at: Character lf put: $n; - at: Character newPage put: $f; - at: Character cr put: $r; - at: Character tab put: $t; - yourself - ] - - ILJson class >> mimeType [ - ^'application/json' - ] - - ILJson class >> newWithConstructors: aCollection [ - | m | - m := Dictionary new. - aCollection do: [:each | - (each isKindOf: Association) - ifTrue: [m add: each] - ifFalse: [m at: each greaseString put: each]]. - ^self new - ctorMap: m; - yourself - ] - - ILJson class >> numbersMayContain: aChar [ - ^aChar isDigit or: [#($- $+ $. $e $E) includes: aChar] - ] - - ILJson class >> readFrom: aStream [ - ^self new readFrom: aStream - ] - - ILJson class >> render: anObject [ - | s | - s := WriteStream on: String new. - anObject printJsonOn: s. - ^s contents - ] - - ILJson class >> render: anObject withConstructor: aConstructorName on: aStream [ - aStream nextPutAll: '@' , aConstructorName. - anObject printJsonOn: aStream - ] - - ILJson class >> renderInstanceVariables: aCollection of: anObject on: aStream [ - | map | - map := Dictionary new. - aCollection - do: [:ivarName | map at: ivarName put: (anObject instVarNamed: ivarName)]. - self - render: map - withConstructor: anObject class name greaseString - on: aStream - ] - - ctorMap [ - - ^ctorMap - ] - - ctorMap: m [ - - ctorMap := m - ] - - stream [ - "Answer the value of stream" - - - ^stream - ] - - stream: anObject [ - "Set the value of stream" - - - stream := anObject - ] - - readAny [ - "This is the main entry point for the JSON parser. See also readFrom: on the class side." - - - | c | - self skipWhitespace. - c := self peek asLowercase. - c == ${ - ifTrue: [ - self next. - ^self readDictionary]. - c == $[ - ifTrue: [ - self next. - ^self readArray]. - c == $" - ifTrue: [ - self next. - ^self readString]. - c == $t ifTrue: [^self consume: 'true' returning: true]. - c == $f ifTrue: [^self consume: 'false' returning: false]. - c == $n ifTrue: [^self consume: 'null' returning: nil]. - c == $@ - ifTrue: [ - self next. - ^self readConstructor]. - (ILJson numbersMayContain: c) ifTrue: [^self readNumber]. - ILJsonSyntaxError signal: 'Unknown Json input' - ] - - readFrom: aStream [ - - self stream: aStream. - ^self readAny - ] - - consume: aString returning: anObject [ - - aString do: [:c | - self next == c ifFalse: [ - ILJsonSyntaxError signal: 'Expected ''' , aString , '''']]. - ^anObject - ] - - interpretStringEscape [ - - | c | - c := self next. - c == $b ifTrue: [^Character backspace]. - c == $n ifTrue: [^Character lf]. - c == $f ifTrue: [^Character newPage]. - c == $r ifTrue: [^Character cr]. - c == $t ifTrue: [^Character tab]. - ^c - ] - - next [ - - ^self stream next - ] - - peek [ - - ^self stream peek - ] - - readArray [ - - | a needComma | - a := OrderedCollection new. - needComma := false. - - [self skipWhitespace. - self peek == $] - ifTrue: [ - self next. - ^a asArray]. - needComma - ifTrue: [ - self peek == $, ifFalse: [ILJsonSyntaxError signal: 'Missing comma']. - self next] - ifFalse: [needComma := true]. - a add: self readAny] - repeat - ] - - readConstructor [ - - | s c v ctor | - s := WriteStream on: ''. - - [c := self peek. - c ifNil: [ - ILJsonSyntaxError signal: 'Premature EOF reading constructor name']. - (c == $. or: [c isLetter]) - ifTrue: [ - s nextPut: c. - self next] - ifFalse: [ - v := self readAny. - s := s contents. - ctor := ctorMap ifNotNil: [ctor := ctorMap at: s ifAbsent: [nil]]. - ctor ifNil: [ILJsonSyntaxError signal: 'Unknown ctor ' , s]. - ^ctor constructFromJson: v]] - repeat - ] - - readDictionary [ - - | m k v needComma | - m := Dictionary new. - needComma := false. - - [self skipWhitespace. - self peek == $} - ifTrue: [self next. ^m]. - needComma - ifTrue: [ - self peek == $, ifFalse: [ILJsonSyntaxError signal: 'Missing comma']. - self next. - self skipWhitespace] - ifFalse: [needComma := true]. - self next == $" - ifFalse: [ILJsonSyntaxError signal: 'Key in dictionary must be string']. - k := self readString. - self skipWhitespace. - self peek == $: ifFalse: [ILJsonSyntaxError signal: 'Missing colon']. - self next. - v := self readAny. - m at: k put: v] - repeat - ] - - readNumber [ - - | acc c | - acc := WriteStream on: ''. - - [c := self peek. - (c isNil not and: [ILJson numbersMayContain: c]) - ifFalse: [[^acc contents asNumber] - on: Error - do: [ILJsonSyntaxError signal: 'Invalid number']]. - acc nextPut: c. - self next] - repeat - ] - - readString [ - - | s c | - s := WriteStream on: ''. - - [c := self next. - c == $\ - ifTrue: [s nextPut: self interpretStringEscape] - ifFalse: [ - c == $" ifTrue: [^s contents]. - s nextPut: c]] - repeat - ] - - skipComment [ - - self peek == $/ - ifTrue: [ - self next. - self peek == $/ - ifTrue: [self skipToEndOfLine] - ifFalse: [ - self peek == $* - ifTrue: [ - self next. - self skipCommentBody] - ifFalse: [ILJsonSyntaxError signal: 'Invalid comment syntax']]] - ] - - skipCommentBody [ - - - [[self next == $*] whileFalse. - self peek == $/] whileFalse. - self next. "skip that last slash" - self skipWhitespace - ] - - skipToEndOfLine [ - - [self peek == Character cr or: [self peek == Character lf]] - whileFalse: [self next]. - self skipWhitespace - ] - - skipWhitespace [ - - [self peek isSeparator] whileTrue: [self next]. - self skipComment - ] -] - -Eval [ - ILJson initialize -] - diff --git a/iliad-stable/Core/lib/JSON/ILJsonObject.st b/iliad-stable/Core/lib/JSON/ILJsonObject.st deleted file mode 100644 index 6ded716..0000000 --- a/iliad-stable/Core/lib/JSON/ILJsonObject.st +++ /dev/null @@ -1,98 +0,0 @@ -"====================================================================== -| -| Iliad.ILJsonObject class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| From Displomacy written by Avi Bryant -| http://www.squeaksource.com/Diplomacy. -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILObject subclass: ILJsonObject [ - | properties | - - - - - initialize [ - - super initialize. - properties := OrderedCollection new - ] - - at: key [ - - ^self at: key ifAbsent: [nil] - ] - - at: key ifAbsent: aBlock [ - - ^(properties - detect: [:ea | ea key = key] - ifNone: [^aBlock value]) value - ] - - at: key put: value [ - - properties add: key -> value - ] - - properties [ - - ^properties - ] - - doesNotUnderstand: aMessage [ - - | key | - key := aMessage selector. - key isUnary - ifTrue: [^self at: key ifAbsent: [super doesNotUnderstand: aMessage]]. - ^(key isKeyword and: [(key occurrencesOf: $:) = 1]) - ifTrue: - [key := key allButLast asSymbol. - self at: key put: aMessage arguments first] - ifFalse: [super doesNotUnderstand: aMessage] - ] - - printJsonOn: aStream [ - aStream nextPut: ${. - properties do: [:ea | - ea key greaseString jsonWriteOn: aStream. - aStream nextPutAll: ': '. - ea value printJsonOn: aStream] - separatedBy: [aStream nextPutAll: ', ']. - aStream nextPut: $} - ] -] - diff --git a/iliad-stable/Core/lib/JSON/ILJsonSyntaxError.st b/iliad-stable/Core/lib/JSON/ILJsonSyntaxError.st deleted file mode 100644 index eb33645..0000000 --- a/iliad-stable/Core/lib/JSON/ILJsonSyntaxError.st +++ /dev/null @@ -1,46 +0,0 @@ -"====================================================================== -| -| Iliad.ILJsonSyntaxError class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| From Displomacy written by Avi Bryant -| http://www.squeaksource.com/Diplomacy. -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -Grease.GRError subclass: ILJsonSyntaxError [ - - - -] - diff --git a/iliad-stable/Core/package.st b/iliad-stable/Core/package.st deleted file mode 100644 index 63cf4e5..0000000 --- a/iliad-stable/Core/package.st +++ /dev/null @@ -1,138 +0,0 @@ -Eval [ - | builder pubDir | - builder := PackageBuilder new - name: 'Iliad-Core'; - namespace: 'Iliad'; - prereq: 'Iconv'; - prereq: 'Grease'; - filein: 'Utilities/ILObject.st'; - filein: 'Utilities/ILComposite.st'; - filein: 'Utilities/ILDynamicVariable.st'; - filein: 'Utilities/ILId.st'; - filein: 'Utilities/ILEncoder.st'; - filein: 'Utilities/ILModelProxy.st'; - - filein: 'lib/HTTP/ILUrl.st'; - filein: 'lib/HTTP/ILFileProxy.st'; - filein: 'lib/HTTP/ILRequest.st'; - filein: 'lib/HTTP/ILResponse.st'; - filein: 'lib/HTTP/ILCookie.st'; - - filein: 'lib/JSON/ILJsonSyntaxError.st'; - filein: 'lib/JSON/ILJson.st'; - filein: 'lib/JSON/ILJsonObject.st'; - filein: 'lib/JSON/Extensions.st'; - - filein: 'Sessions/ILUrlBuilder.st'; - filein: 'Sessions/ILContext.st'; - filein: 'Sessions/ILAction.st'; - filein: 'Sessions/ILCurrentContext.st'; - filein: 'Sessions/ILActionRegistry.st'; - filein: 'Sessions/ILStateRegistry.st'; - filein: 'Sessions/ILSession.st'; - filein: 'Sessions/ILSessionManager.st'; - - filein: 'Elements/ILElements-Error.st'; - filein: 'Elements/ILElement.st'; - filein: 'Elements/ILTextElement.st'; - filein: 'Elements/ILXmlElement.st'; - filein: 'Elements/Extensions.st'; - - filein: 'HTMLElements/ILHTMLBuilderElement.st'; - filein: 'HTMLElements/ILTitleElement.st'; - filein: 'HTMLElements/ILBodyElement.st'; - filein: 'HTMLElements/ILClosingElement.st'; - filein: 'HTMLElements/ILAreaElement.st'; - filein: 'HTMLElements/ILBreakElement.st'; - filein: 'HTMLElements/ILHorizontalRuleElement.st'; - filein: 'HTMLElements/ILImageElement.st'; - filein: 'HTMLElements/ILMetaElement.st'; - filein: 'HTMLElements/ILParameterElement.st'; - filein: 'HTMLElements/ILDirectionElement.st'; - filein: 'HTMLElements/ILDivElement.st'; - filein: 'HTMLElements/ILFieldsetElement.st'; - filein: 'HTMLElements/ILFormElement.st'; - filein: 'HTMLElements/ILFormElementElement.st'; - filein: 'HTMLElements/ILButtonElement.st'; - filein: 'HTMLElements/ILCheckboxElement.st'; - filein: 'HTMLElements/ILRadioButtonElement.st'; - filein: 'HTMLElements/ILInputElement.st'; - filein: 'HTMLElements/ILSelectElement.st'; - filein: 'HTMLElements/ILTextAreaElement.st'; - filein: 'HTMLElements/ILHeadElement.st'; - filein: 'HTMLElements/ILHeadingElement.st'; - filein: 'HTMLElements/ILHtmlElement.st'; - filein: 'HTMLElements/ILLabelElement.st'; - filein: 'HTMLElements/ILLegendElement.st'; - filein: 'HTMLElements/ILLinkableElement.st'; - filein: 'HTMLElements/ILAnchorElement.st'; - filein: 'HTMLElements/ILLinkElement.st'; - filein: 'HTMLElements/ILListElement.st'; - filein: 'HTMLElements/ILListItemElement.st'; - filein: 'HTMLElements/ILMapElement.st'; - filein: 'HTMLElements/ILObjectElement.st'; - filein: 'HTMLElements/ILOptionElement.st'; - filein: 'HTMLElements/ILOptionGroupElement.st'; - filein: 'HTMLElements/ILParagraphElement.st'; - filein: 'HTMLElements/ILRawHtmlElement.st'; - filein: 'HTMLElements/ILRubyTextElement.st'; - filein: 'HTMLElements/ILScriptElement.st'; - filein: 'HTMLElements/ILSpanElement.st'; - filein: 'HTMLElements/ILTableElement.st'; - filein: 'HTMLElements/ILTableElementElement.st'; - filein: 'HTMLElements/ILTableBodyElement.st'; - filein: 'HTMLElements/ILTableCellElement.st'; - filein: 'HTMLElements/ILTableDataElement.st'; - filein: 'HTMLElements/ILTableHeaderElement.st'; - filein: 'HTMLElements/ILTableRowElement.st'; - filein: 'HTMLElements/ILTableFootElement.st'; - filein: 'HTMLElements/ILTableHeadElement.st'; - filein: 'HTMLElements/ILConditionalCommentElement.st'; - - filein: 'Buildables/Extensions.st'; - filein: 'Buildables/ILBuildable.st'; - filein: 'Buildables/ILDecorator.st'; - filein: 'Buildables/ILAnswerHandler.st'; - filein: 'Buildables/ILDelegator.st'; - filein: 'Buildables/ILAppendDelegator.st'; - filein: 'Buildables/ILPrependDelegator.st'; - filein: 'Buildables/ILWidget.st'; - filein: 'Buildables/ILSequence.st'; - filein: 'Buildables/ILInformationWidget.st'; - filein: 'Buildables/ILConfirmationWidget.st'; - filein: 'Buildables/ILPluggableWidget.st'; - filein: 'Buildables/ILProfiler.st'; - filein: 'Buildables/ILApplication.st'; - filein: 'Buildables/ILHTMLPage.st'; - filein: 'Buildables/ILCurrentBuildable.st'; - - filein: 'Dispatching/ILDispatchError.st'; - filein: 'Dispatching/ILDispatcher.st'; - filein: 'Dispatching/ILRouter.st'; - filein: 'Dispatching/ILRoute.st'; - - filein: 'RequestHandlers/ILResponseNotification.st'; - filein: 'RequestHandlers/ILRequestHandler.st'; - filein: 'RequestHandlers/ILErrorHandler.st'; - filein: 'RequestHandlers/ILDirectory.st'; - filein: 'RequestHandlers/ILMemoryDirectory.st'; - filein: 'RequestHandlers/ILFileHandler.st'; - filein: 'RequestHandlers/ILNotFoundHandler.st'; - filein: 'RequestHandlers/ILJsonHandler.st'; - filein: 'RequestHandlers/ILApplicationHandler.st'; - filein: 'RequestHandlers/ILRedirectHandler.st'; - - filein: 'GST/ILDiskDirectory.st'; - filein: 'GST/Extensions.st'; - - filein: 'postLoad.st'; - - yourself. - - pubDir := Directory working / 'Public'. - pubDir all do: [:each | - each isFile ifTrue: [ - builder resource: (each pathFrom: Directory working)]]. - - builder buildXml -] diff --git a/iliad-stable/Core/package.xml b/iliad-stable/Core/package.xml deleted file mode 100644 index 1d0e82b..0000000 --- a/iliad-stable/Core/package.xml +++ /dev/null @@ -1,255 +0,0 @@ - - Iliad-Core - Iliad - Iconv - Grease - Utilities/ILObject.st - Utilities/ILComposite.st - Utilities/ILDynamicVariable.st - Utilities/ILId.st - Utilities/ILEncoder.st - Utilities/ILModelProxy.st - lib/HTTP/ILUrl.st - lib/HTTP/ILFileProxy.st - lib/HTTP/ILRequest.st - lib/HTTP/ILResponse.st - lib/HTTP/ILCookie.st - lib/JSON/ILJsonSyntaxError.st - lib/JSON/ILJson.st - lib/JSON/ILJsonObject.st - lib/JSON/Extensions.st - Sessions/ILUrlBuilder.st - Sessions/ILContext.st - Sessions/ILAction.st - Sessions/ILCurrentContext.st - Sessions/ILActionRegistry.st - Sessions/ILStateRegistry.st - Sessions/ILSession.st - Sessions/ILSessionManager.st - Elements/ILElements-Error.st - Elements/ILElement.st - Elements/ILTextElement.st - Elements/ILXmlElement.st - Elements/Extensions.st - HTMLElements/ILHTMLBuilderElement.st - HTMLElements/ILTitleElement.st - HTMLElements/ILBodyElement.st - HTMLElements/ILClosingElement.st - HTMLElements/ILAreaElement.st - HTMLElements/ILBreakElement.st - HTMLElements/ILHorizontalRuleElement.st - HTMLElements/ILImageElement.st - HTMLElements/ILMetaElement.st - HTMLElements/ILParameterElement.st - HTMLElements/ILDirectionElement.st - HTMLElements/ILDivElement.st - HTMLElements/ILFieldsetElement.st - HTMLElements/ILFormElement.st - HTMLElements/ILFormElementElement.st - HTMLElements/ILButtonElement.st - HTMLElements/ILCheckboxElement.st - HTMLElements/ILRadioButtonElement.st - HTMLElements/ILInputElement.st - HTMLElements/ILSelectElement.st - HTMLElements/ILTextAreaElement.st - HTMLElements/ILHeadElement.st - HTMLElements/ILHeadingElement.st - HTMLElements/ILHtmlElement.st - HTMLElements/ILLabelElement.st - HTMLElements/ILLegendElement.st - HTMLElements/ILLinkableElement.st - HTMLElements/ILAnchorElement.st - HTMLElements/ILLinkElement.st - HTMLElements/ILListElement.st - HTMLElements/ILListItemElement.st - HTMLElements/ILMapElement.st - HTMLElements/ILObjectElement.st - HTMLElements/ILOptionElement.st - HTMLElements/ILOptionGroupElement.st - HTMLElements/ILParagraphElement.st - HTMLElements/ILRawHtmlElement.st - HTMLElements/ILRubyTextElement.st - HTMLElements/ILScriptElement.st - HTMLElements/ILSpanElement.st - HTMLElements/ILTableElement.st - HTMLElements/ILTableElementElement.st - HTMLElements/ILTableBodyElement.st - HTMLElements/ILTableCellElement.st - HTMLElements/ILTableDataElement.st - HTMLElements/ILTableHeaderElement.st - HTMLElements/ILTableRowElement.st - HTMLElements/ILTableFootElement.st - HTMLElements/ILTableHeadElement.st - HTMLElements/ILConditionalCommentElement.st - Buildables/Extensions.st - Buildables/ILBuildable.st - Buildables/ILDecorator.st - Buildables/ILAnswerHandler.st - Buildables/ILDelegator.st - Buildables/ILAppendDelegator.st - Buildables/ILPrependDelegator.st - Buildables/ILWidget.st - Buildables/ILSequence.st - Buildables/ILInformationWidget.st - Buildables/ILConfirmationWidget.st - Buildables/ILPluggableWidget.st - Buildables/ILProfiler.st - Buildables/ILApplication.st - Buildables/ILHTMLPage.st - Buildables/ILCurrentBuildable.st - Dispatching/ILDispatchError.st - Dispatching/ILDispatcher.st - Dispatching/ILRouter.st - Dispatching/ILRoute.st - RequestHandlers/ILResponseNotification.st - RequestHandlers/ILRequestHandler.st - RequestHandlers/ILErrorHandler.st - RequestHandlers/ILDirectory.st - RequestHandlers/ILMemoryDirectory.st - RequestHandlers/ILFileHandler.st - RequestHandlers/ILNotFoundHandler.st - RequestHandlers/ILJsonHandler.st - RequestHandlers/ILApplicationHandler.st - RequestHandlers/ILRedirectHandler.st - GST/ILDiskDirectory.st - GST/Extensions.st - postLoad.st - Utilities/ILObject.st - Utilities/ILComposite.st - Utilities/ILDynamicVariable.st - Utilities/ILId.st - Utilities/ILEncoder.st - Utilities/ILModelProxy.st - lib/HTTP/ILUrl.st - lib/HTTP/ILFileProxy.st - lib/HTTP/ILRequest.st - lib/HTTP/ILResponse.st - lib/HTTP/ILCookie.st - lib/JSON/ILJsonSyntaxError.st - lib/JSON/ILJson.st - lib/JSON/ILJsonObject.st - lib/JSON/Extensions.st - Sessions/ILUrlBuilder.st - Sessions/ILContext.st - Sessions/ILAction.st - Sessions/ILCurrentContext.st - Sessions/ILActionRegistry.st - Sessions/ILStateRegistry.st - Sessions/ILSession.st - Sessions/ILSessionManager.st - Elements/ILElements-Error.st - Elements/ILElement.st - Elements/ILTextElement.st - Elements/ILXmlElement.st - Elements/Extensions.st - HTMLElements/ILHTMLBuilderElement.st - HTMLElements/ILTitleElement.st - HTMLElements/ILBodyElement.st - HTMLElements/ILClosingElement.st - HTMLElements/ILAreaElement.st - HTMLElements/ILBreakElement.st - HTMLElements/ILHorizontalRuleElement.st - HTMLElements/ILImageElement.st - HTMLElements/ILMetaElement.st - HTMLElements/ILParameterElement.st - HTMLElements/ILDirectionElement.st - HTMLElements/ILDivElement.st - HTMLElements/ILFieldsetElement.st - HTMLElements/ILFormElement.st - HTMLElements/ILFormElementElement.st - HTMLElements/ILButtonElement.st - HTMLElements/ILCheckboxElement.st - HTMLElements/ILRadioButtonElement.st - HTMLElements/ILInputElement.st - HTMLElements/ILSelectElement.st - HTMLElements/ILTextAreaElement.st - HTMLElements/ILHeadElement.st - HTMLElements/ILHeadingElement.st - HTMLElements/ILHtmlElement.st - HTMLElements/ILLabelElement.st - HTMLElements/ILLegendElement.st - HTMLElements/ILLinkableElement.st - HTMLElements/ILAnchorElement.st - HTMLElements/ILLinkElement.st - HTMLElements/ILListElement.st - HTMLElements/ILListItemElement.st - HTMLElements/ILMapElement.st - HTMLElements/ILObjectElement.st - HTMLElements/ILOptionElement.st - HTMLElements/ILOptionGroupElement.st - HTMLElements/ILParagraphElement.st - HTMLElements/ILRawHtmlElement.st - HTMLElements/ILRubyTextElement.st - HTMLElements/ILScriptElement.st - HTMLElements/ILSpanElement.st - HTMLElements/ILTableElement.st - HTMLElements/ILTableElementElement.st - HTMLElements/ILTableBodyElement.st - HTMLElements/ILTableCellElement.st - HTMLElements/ILTableDataElement.st - HTMLElements/ILTableHeaderElement.st - HTMLElements/ILTableRowElement.st - HTMLElements/ILTableFootElement.st - HTMLElements/ILTableHeadElement.st - HTMLElements/ILConditionalCommentElement.st - Buildables/Extensions.st - Buildables/ILBuildable.st - Buildables/ILDecorator.st - Buildables/ILAnswerHandler.st - Buildables/ILDelegator.st - Buildables/ILAppendDelegator.st - Buildables/ILPrependDelegator.st - Buildables/ILWidget.st - Buildables/ILSequence.st - Buildables/ILInformationWidget.st - Buildables/ILConfirmationWidget.st - Buildables/ILPluggableWidget.st - Buildables/ILProfiler.st - Buildables/ILApplication.st - Buildables/ILHTMLPage.st - Buildables/ILCurrentBuildable.st - Dispatching/ILDispatchError.st - Dispatching/ILDispatcher.st - Dispatching/ILRouter.st - Dispatching/ILRoute.st - RequestHandlers/ILResponseNotification.st - RequestHandlers/ILRequestHandler.st - RequestHandlers/ILErrorHandler.st - RequestHandlers/ILDirectory.st - RequestHandlers/ILMemoryDirectory.st - RequestHandlers/ILFileHandler.st - RequestHandlers/ILNotFoundHandler.st - RequestHandlers/ILJsonHandler.st - RequestHandlers/ILApplicationHandler.st - RequestHandlers/ILRedirectHandler.st - GST/ILDiskDirectory.st - GST/Extensions.st - postLoad.st - Public/stylesheets/jquery-ui-1.9.2.css - Public/stylesheets/images/ui-bg_glass_65_ffffff_1x400.png - Public/stylesheets/images/ui-icons_222222_256x240.png - Public/stylesheets/images/ui-bg_flat_0_aaaaaa_40x100.png - Public/stylesheets/images/ui-bg_glass_75_e6e6e6_1x400.png - Public/stylesheets/images/ui-icons_454545_256x240.png - Public/stylesheets/images/ui-icons_888888_256x240.png - Public/stylesheets/images/ui-icons_2e83ff_256x240.png - Public/stylesheets/images/ui-bg_glass_95_fef1ec_1x400.png - Public/stylesheets/images/ui-bg_flat_75_ffffff_40x100.png - Public/stylesheets/images/ui-bg_glass_55_fbf9ee_1x400.png - Public/stylesheets/images/ui-bg_glass_75_dadada_1x400.png - Public/stylesheets/images/ui-bg_highlight-soft_75_cccccc_1x100.png - Public/stylesheets/images/ui-icons_cd0a0a_256x240.png - Public/stylesheets/iliad.css - Public/images/ajax_loader.gif - Public/images/iliad_big.png - Public/images/iliad_small.png - Public/images/iliad_tiny.png - Public/images/iliad_huge.png - Public/images/iliad.png - Public/images/iliad_bleached.png - Public/javascripts/jquery-1.8.3.min.js - Public/javascripts/jquery-ui-1.9.2.js - Public/javascripts/no_conflict.js - Public/javascripts/iliad_ie_history.html - Public/javascripts/iliad.js - diff --git a/iliad-stable/Core/postLoad.st b/iliad-stable/Core/postLoad.st deleted file mode 100644 index 6ced8c9..0000000 --- a/iliad-stable/Core/postLoad.st +++ /dev/null @@ -1,11 +0,0 @@ -Eval [ - (Directory image / 'Public') exists ifTrue: [ - ILFileHandler addDirectory: - (ILDiskDirectory new - directory: (Directory image / 'Public'); - yourself)]. - ILFileHandler addDirectory: - (ILDiskDirectory new - directory: (PackageLoader packageAt: 'Iliad-Core') directory / 'Public'; - yourself). -] diff --git a/iliad-stable/More/Comet/Extensions.st b/iliad-stable/More/Comet/Extensions.st deleted file mode 100644 index ec29d1d..0000000 --- a/iliad-stable/More/Comet/Extensions.st +++ /dev/null @@ -1,40 +0,0 @@ -ILWidget extend [ - - subscribeToCometEvent: anEventClass [ - "Register the receiver to push its contents to the client when the event occurs." - - - self session cometHandler - subscribe: self - to: anEventClass - ] - - triggerCometEvent: anEvent [ - "Update all widgets which registered to the event " - - self session cometHandler triggerEvent: anEvent - ] - - handleCometEvent: anEvent [ - - self markDirty - ] -] - -ILApplication extend [ - - cometConnection [ - - ^self - attributeAt: #cometConnection - ifAbsentPut: [ILCometConnectionWidget new] - ] -] - -ILSession extend [ - - cometHandler [ - - ^self otherAt: #cometHandler ifAbsentPut: [ILCometHandler on: self] - ] -] diff --git a/iliad-stable/More/Comet/ILCometConnectionWidget.st b/iliad-stable/More/Comet/ILCometConnectionWidget.st deleted file mode 100644 index bc2b7bf..0000000 --- a/iliad-stable/More/Comet/ILCometConnectionWidget.st +++ /dev/null @@ -1,21 +0,0 @@ -ILWidget subclass: ILCometConnectionWidget [ - - handler [ - - ^self session cometHandler - ] - - push [ - - self handler waitForEvent. - self markDirty - ] - - contents [ - - ^[:e || action | - action := self session registerActionFor: [self push]. - e script: 'jQuery(document).ready(function() {iliad.evaluateAction("', (self context urlBuilder urlForAction: action) greaseString, '", "get", "", false)})'] - ] -] - diff --git a/iliad-stable/More/Comet/ILCometEvent.st b/iliad-stable/More/Comet/ILCometEvent.st deleted file mode 100644 index e3c1ed4..0000000 --- a/iliad-stable/More/Comet/ILCometEvent.st +++ /dev/null @@ -1,7 +0,0 @@ -ILObject subclass: ILCometEvent [ - - - - -] - diff --git a/iliad-stable/More/Comet/ILCometHandler.st b/iliad-stable/More/Comet/ILCometHandler.st deleted file mode 100644 index 5383e0b..0000000 --- a/iliad-stable/More/Comet/ILCometHandler.st +++ /dev/null @@ -1,162 +0,0 @@ -"====================================================================== -| -| Iliad.ILCometHandler class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILObject subclass: ILCometHandler [ - | session subscriptions semaphores shouldPush| - - - - - ILCometHandler class [ - | pingProcess | - - on: aSession [ - - ^self new - session: aSession; - yourself - ] - - initialize [ - - Grease.GRPlatform current addToStartUpList: self. - Grease.GRPlatform current addToShutDownList: self. - self startUp: true. - ] - - sessionManager [ - - ^ILSessionManager current - ] - - startUp: isStarting [ - - isStarting ifTrue: [ - self shutDown: true. - pingProcess := [[self pingClients] repeat] fork] - ] - - shutDown: isDown [ - - isDown ifTrue: [ - pingProcess ifNotNil: [ - pingProcess terminate. - pingProcess := nil]] - ] - - pingClients [ - - (Delay forSeconds: 3 * 60) wait. - self sessionManager sessions do: [:each | - each cometHandler push] - ] - - ] - - initialize [ - - super initialize. - shouldPush := false. - semaphores := OrderedCollection new. - subscriptions := OrderedCollection new - ] - - session [ - - ^session - ] - - session: aSession [ - - session := aSession - ] - - sessionManager [ - - ^self class sessionManager - ] - - otherHandlers [ - - ^(self sessionManager sessions - copyWithout: self session) collect: [:each | - each cometHandler] - ] - - subscribe: aWidget to: anEventClass [ - - subscriptions add: (ILCometSubscription new - handler: self; - widget: aWidget; - eventClass: anEventClass) - ] - - triggerEvent: anEvent [ - - self otherHandlers do: [:each | - each handleEvent: anEvent] - ] - - handleEvent: anEvent [ - - subscriptions do: [:each | each handleEvent: anEvent]. - shouldPush ifTrue: [self push] - ] - - waitForEvent [ - - | s | - s := Semaphore new. - semaphores add: s. - s wait - ] - - push [ - - semaphores do: [:each | each signal]. - semaphores := OrderedCollection new. - shouldPush := false - ] - - shouldPush [ - - shouldPush := true - ] -] - -Eval [ILCometHandler initialize] diff --git a/iliad-stable/More/Comet/ILCometSubscription.st b/iliad-stable/More/Comet/ILCometSubscription.st deleted file mode 100644 index 3e9416f..0000000 --- a/iliad-stable/More/Comet/ILCometSubscription.st +++ /dev/null @@ -1,48 +0,0 @@ -ILObject subclass: ILCometSubscription [ - | handler widget eventClass | - - - - handler: aCometHandler [ - - handler := aCometHandler - ] - - handler [ - - ^handler - ] - - session [ - - ^self handler session - ] - - widget [ - - ^widget - ] - - widget: aWidget [ - - widget := aWidget - ] - - eventClass [ - - ^eventClass - ] - - eventClass: aClass [ - - eventClass := aClass - ] - - handleEvent: anEvent [ - - (anEvent isKindOf: self eventClass) ifTrue: [ - self widget handleCometEvent: anEvent. - self handler shouldPush] - ] -] - diff --git a/iliad-stable/More/Comet/package.st b/iliad-stable/More/Comet/package.st deleted file mode 100644 index 61ed998..0000000 --- a/iliad-stable/More/Comet/package.st +++ /dev/null @@ -1,14 +0,0 @@ -Eval [ - PackageBuilder new - name: 'Iliad-More-Comet'; - namespace: 'Iliad'; - prereq: 'Iliad-Core'; - - filein: 'ILCometHandler.st'; - filein: 'ILCometEvent.st'; - filein: 'ILCometSubscription.st'; - filein: 'ILCometConnectionWidget.st'; - filein: 'Extensions.st'; - - buildXml -] diff --git a/iliad-stable/More/Comet/package.xml b/iliad-stable/More/Comet/package.xml deleted file mode 100644 index f84b513..0000000 --- a/iliad-stable/More/Comet/package.xml +++ /dev/null @@ -1,15 +0,0 @@ - - Iliad-More-Comet - Iliad - Iliad-Core - ILCometHandler.st - ILCometEvent.st - ILCometSubscription.st - ILCometConnectionWidget.st - Extensions.st - ILCometHandler.st - ILCometEvent.st - ILCometSubscription.st - ILCometConnectionWidget.st - Extensions.st - diff --git a/iliad-stable/More/Examples/ILCometCounter.st b/iliad-stable/More/Examples/ILCometCounter.st deleted file mode 100644 index a878989..0000000 --- a/iliad-stable/More/Examples/ILCometCounter.st +++ /dev/null @@ -1,82 +0,0 @@ -ILApplication subclass: ILCometCounterApplication [ - | counter | - - ILCometCounterApplication class >> path [^'examples/comet'] - - initialize [ - super initialize. - counter := ILCometCounter new - ] - - index [ - - ^[:e | - e - build: self cometConnection; - build: counter] - ] -] - - -ILObject subclass: ILCounterModel [ - | count | - - - ILCounterModel class [ - | instance | - - instance [ - instance ifNil: [instance := self new]. - ^instance - ] - ] - - initialize [ - super initialize. - count := 0 - ] - - count [ - ^count - ] - - increase [ - count := count + 1 - ] - - decrease [ - count := count -1 - ] -] - -ILCometEvent subclass: ILCounterChangedEvent [] - - -Iliad.ILWidget subclass: ILCometCounter [ - | counter | - - initialize [ - super initialize. - counter := ILCounterModel instance. - self subscribeToCometEvent: ILCounterChangedEvent - ] - - contents [ - ^[:e | - e h1: counter count printString. - e a action: [self increase]; text: '++'. - e a action: [self decrease]; text: '--'] - ] - - increase [ - counter increase. - self markDirty. - self triggerCometEvent: ILCounterChangedEvent new - ] - - decrease [ - counter decrease. - self markDirty. - self triggerCometEvent: ILCounterChangedEvent new - ] -] diff --git a/iliad-stable/More/Examples/ILCounter.st b/iliad-stable/More/Examples/ILCounter.st deleted file mode 100644 index 6fc98b2..0000000 --- a/iliad-stable/More/Examples/ILCounter.st +++ /dev/null @@ -1,71 +0,0 @@ -"====================================================================== -| -| Iliad.ILCounter class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILWidget subclass: ILCounter [ - | count | - - - - - initialize [ - - super initialize. - count := 0 - ] - - contents [ - - ^[:e | - e h1: count greaseString. - e a action: [self increase]; text: '++'. - e space. - e a action: [self decrease]; text: '--'] - ] - - decrease [ - - count := count - 1. - self markDirty - ] - - increase [ - - count := count + 1. - self markDirty - ] -] - diff --git a/iliad-stable/More/Examples/ILCounterApplication.st b/iliad-stable/More/Examples/ILCounterApplication.st deleted file mode 100644 index 24fe4d5..0000000 --- a/iliad-stable/More/Examples/ILCounterApplication.st +++ /dev/null @@ -1,88 +0,0 @@ -"====================================================================== -| -| Iliad.ILCounterApplication class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILApplication subclass: ILCounterApplication [ - | counters | - - - - - ILCounterApplication class >> path [ - - ^'examples/counters' - ] - - index [ - - ^self counter - ] - - counter [ - - ^[:e | - e a - text: 'Switch to multi counter example'; - linkToLocal: 'multicounter'. - e build: self counters first] - ] - - multicounter [ - - ^[:e | - e a - text: 'Switch to simple counter example'; - linkToLocal: 'counter'. - self counters do: [:each | - e build: each]] - ] - - counters [ - - ^counters ifNil: [ - counters := {ILCounter new. - ILCounter new. - ILCounter new. - ILCounter new}] - ] - - updatePage: aPage [ - - super updatePage: aPage. - aPage head stylesheet href: '/stylesheets/iliad.css' - ] -] - diff --git a/iliad-stable/More/Examples/ILGravatarWidget.st b/iliad-stable/More/Examples/ILGravatarWidget.st deleted file mode 100644 index d48965e..0000000 --- a/iliad-stable/More/Examples/ILGravatarWidget.st +++ /dev/null @@ -1,104 +0,0 @@ -ILWidget subclass: ILGravatarWidget [ - | emailAddress options | - - - - - - ILGravatarWidget class [ - - for: aString [ - - ^self new - emailAddress: aString; - yourself - ] - - hostname [ - - ^'http://www.gravatar.com/avatar/' - ] - ] - - emailAddress [ - - ^emailAddress - ] - - emailAddress: aString [ - - emailAddress := aString - ] - - hostname [ - - ^self class hostname - ] - - gravatarId [ - - ^MD5 hexDigestOf: self emailAddress - ] - - url [ - - | stream | - stream := WriteStream on: ''. - stream - nextPutAll: self hostname; - nextPutAll: self gravatarId. - self options keysAndValuesDo: [:key :value | - stream - nextPut: $?; - nextPutAll: key; - nextPut: $=. - ILEncoder encodeUrl: value on: stream]. - ^stream contents - ] - - options [ - - ^options ifNil: [options := Dictionary new] - ] - - size [ - - ^self options at: #size ifAbsent: [nil] - ] - - size: anInteger [ - - self options at: #size put: anInteger greaseString - ] - - rating [ - - ^self options at: #rating ifAbsent: [nil] - ] - - rating: aString [ - - self options at: #rating put: aString - ] - - default [ - - ^self options at: #default ifAbsent: [nil] - ] - - default: aString [ - - self options at: #default put: aString - ] - - contents [ - - ^[:e | - e div - class: 'gravatar'; - build: [:div | - div img - src: self url; - alt: self emailAddress]] - ] -] diff --git a/iliad-stable/More/Examples/ILTodoListApplication.st b/iliad-stable/More/Examples/ILTodoListApplication.st deleted file mode 100644 index e7c706f..0000000 --- a/iliad-stable/More/Examples/ILTodoListApplication.st +++ /dev/null @@ -1,118 +0,0 @@ -"====================================================================== -| -| Iliad.ILTodoListApplication class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILApplication subclass: ILTodoListApplication [ - | todoListGridWidget | - - - - - ILTodoListApplication class >> path [ - - ^'examples/todo' - ] - - selectCompleted [ - - self todoListGridWidget selectBlock: [:item | item completed]. - self todoListGridWidget markDirty - ] - - selectPending [ - - self todoListGridWidget selectBlock: [:item | item completed not]. - self todoListGridWidget markDirty - ] - - todoListGridWidget [ - - ^todoListGridWidget ifNil: [todoListGridWidget := ILTodoListGridWidget new] - ] - - initialize [ - - super initialize. - self model: ILTodoListItemRepository default - ] - - updateFromHash [ - - | path | - path := self router hashRoute next. - path = 'pending' ifTrue: [self selectPending]. - path = 'completed' ifTrue: [self selectCompleted] - ] - - updatePage: aPage [ - - super updatePage: aPage. - aPage head stylesheet href: '/stylesheets/iliad.css' - ] - - index [ - - self updateFromHash. - ^self mainContents - ] - - mainContents [ - - ^[:e | - e div - class: 'wrapper'; - build: [:div | - div h1: 'Todo List'. - div build: self actionLinksContents. - div build: self todoListGridWidget]] - ] - - actionLinksContents [ - - ^[:e ||div| - div := e div class: 'selection'; yourself. - div a - action: [self selectPending] - hash: 'pending'; - text: 'pending'. - div space. - div a - action: [self selectCompleted] - hash: 'completed'; - text: 'completed'. - e br] - ] -] diff --git a/iliad-stable/More/Examples/ILTodoListGridWidget.st b/iliad-stable/More/Examples/ILTodoListGridWidget.st deleted file mode 100644 index c417363..0000000 --- a/iliad-stable/More/Examples/ILTodoListGridWidget.st +++ /dev/null @@ -1,145 +0,0 @@ -"====================================================================== -| -| Iliad.ILTodoListGridWidget class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILWidget subclass: ILTodoListGridWidget [ - | selectBlock dataGrid | - - - - - addNewItem [ - - | newItem | - newItem := ILTodoListItem new. - self lightbox: ((self formulaForItem: newItem) - addMessage: [:e | e h2: 'Add item ', newItem title]; - yourself) - onAnswer: [:item | item ifNotNil: [ - self application model addItem: item. - self updateDataGridItems]] - ] - - editItem: anItem [ - - self lightbox: ((self formulaForItem: anItem) - addMessage: [:e | e h2: 'Edit item ', anItem title]; - yourself) - ] - - removeItem: anItem [ - - self application model removeItem: anItem. - self markDirty - ] - - setItem: anItem completed: aBoolean [ - - anItem completed: aBoolean. - self updateDataGridItems - ] - - updateDataGridItems [ - - self dataGrid items: - (self items asSortedCollection: [:a :b | a deadline < b deadline]) - ] - - contents [ - - ^[:e | - self updateDataGridItems. - e build: self dataGrid. - e div a - action: [self addNewItem]; - text: 'new'] - ] - - formulaForItem: anItem [ - - | formula | - formula := ILFormula on: anItem. - (formula dateInputOn: #deadline) - label: 'Deadline'. - (formula inputOn: #title) - labelContents: [:e | e span class: 'required';text: 'Title']; - addCondition: [:val | val notNil and: [val notEmpty]] - labelled: [:val | 'This field is required']. - (formula textareaOn: #body) - labelContents: [:e | e span class: 'required';text: 'Body']; - size: 30@10; - addCondition: [:val | val notNil and: [val notEmpty]] - labelled: [:val | 'This field is required']. - (formula checkboxOn: #completed) - label: 'Completed'. - ^formula - ] - - dataGrid [ - - ^dataGrid ifNil: [ - dataGrid := (ILPagedDataGrid new - items: (self items asSortedCollection: [:a :b | a deadline < b deadline]); - columnNames: #('' 'Title' 'Body' 'Deadline' '' ''); - column: 1 buildContents: [:e :item | e form checkbox - checked: item completed; - beSubmitOnClick; - action: [:val | self setItem: item completed: val]]; - column: 2 buildContents: [:e :item | e text: item title]; - column: 3 buildContents: [:e :item | e text: item body]; - column: 4 buildContents: [:e :item | e text: item deadline greaseString]; - column: 5 buildContents: [:e :item | e a text: 'Edit'; action: [self editItem: item]]; - column: 6 buildContents: [:e :item | e a text: 'Remove'; action: [self removeItem: item]]; - rowsPerPage: 3; - yourself)] - ] - - items [ - - ^self application model items select: self selectBlock - ] - - selectBlock [ - - ^selectBlock ifNil: [selectBlock := [:each | each completed not]] - ] - - selectBlock: aBlock [ - - selectBlock := aBlock - ] -] - diff --git a/iliad-stable/More/Examples/ILTodoListItem.st b/iliad-stable/More/Examples/ILTodoListItem.st deleted file mode 100644 index bcb388e..0000000 --- a/iliad-stable/More/Examples/ILTodoListItem.st +++ /dev/null @@ -1,84 +0,0 @@ -"====================================================================== -| -| Iliad.ILTodoListItem class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -Object subclass: ILTodoListItem [ - | deadline title body completed | - - - - - completed [ - - ^completed ifNil: [false] - ] - - completed: aBoolean [ - - completed := aBoolean - ] - - deadline [ - - ^deadline ifNil: [deadline := Date today] - ] - - deadline: aDeadline [ - - deadline := aDeadline - ] - - body [ - - ^body ifNil: [''] - ] - - body: aString [ - - body := aString - ] - - title [ - - ^title ifNil: [''] - ] - - title: aString [ - - title := aString - ] -] - diff --git a/iliad-stable/More/Examples/ILTodoListItemRepository.st b/iliad-stable/More/Examples/ILTodoListItemRepository.st deleted file mode 100644 index b1aa4c2..0000000 --- a/iliad-stable/More/Examples/ILTodoListItemRepository.st +++ /dev/null @@ -1,65 +0,0 @@ -"====================================================================== -| -| Iliad.ILTodoListItemRepository class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -Object subclass: ILTodoListItemRepository [ - | items | - - - - - ILTodoListItemRepository class [ - | default | - - ] - - ILTodoListItemRepository class >> default [ - ^default ifNil: [default := self new] - ] - - addItem: anItem [ - self items add: anItem - ] - - items [ - ^items ifNil: [items := OrderedCollection new] - ] - - removeItem: anItem [ - self items remove: anItem - ] -] - diff --git a/iliad-stable/More/Examples/package.st b/iliad-stable/More/Examples/package.st deleted file mode 100644 index c173f12..0000000 --- a/iliad-stable/More/Examples/package.st +++ /dev/null @@ -1,21 +0,0 @@ -Eval [ - PackageBuilder new - name: 'Iliad-More-Examples'; - namespace: 'Iliad'; - prereq: 'Iliad-Core'; - prereq: 'Iliad-More-UI'; - prereq: 'Iliad-More-Formula'; - prereq: 'Iliad-More-Comet'; - prereq: 'Digest'; - - filein: 'ILCounter.st'; - filein: 'ILCounterApplication.st'; - filein: 'ILTodoListItem.st'; - filein: 'ILTodoListItemRepository.st'; - filein: 'ILTodoListGridWidget.st'; - filein: 'ILTodoListApplication.st'; - filein: 'ILGravatarWidget.st'; - filein: 'ILCometCounter.st'; - - buildXml -] diff --git a/iliad-stable/More/Examples/package.xml b/iliad-stable/More/Examples/package.xml deleted file mode 100644 index 452ebfc..0000000 --- a/iliad-stable/More/Examples/package.xml +++ /dev/null @@ -1,25 +0,0 @@ - - Iliad-More-Examples - Iliad - Iliad-Core - Iliad-More-UI - Iliad-More-Formula - Iliad-More-Comet - Digest - ILCounter.st - ILCounterApplication.st - ILTodoListItem.st - ILTodoListItemRepository.st - ILTodoListGridWidget.st - ILTodoListApplication.st - ILGravatarWidget.st - ILCometCounter.st - ILCounter.st - ILCounterApplication.st - ILTodoListItem.st - ILTodoListItemRepository.st - ILTodoListGridWidget.st - ILTodoListApplication.st - ILGravatarWidget.st - ILCometCounter.st - diff --git a/iliad-stable/More/Formula/ILAutocompleteInputField.st b/iliad-stable/More/Formula/ILAutocompleteInputField.st deleted file mode 100644 index 760afd4..0000000 --- a/iliad-stable/More/Formula/ILAutocompleteInputField.st +++ /dev/null @@ -1,84 +0,0 @@ -"====================================================================== -| -| Iliad.ILAutocompleterInputField class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILField subclass: ILAutocompleteInputField [ - | options fieldId | - - - - - initialize [ - - super initialize. - fieldId := ILId new - ] - - options [ - - ^options ifNil: [#()] - ] - - options: aCollection [ - - options := aCollection - ] - - completerScript [ - - | str | - str := WriteStream on: ''. - str nextPutAll: ' - jQuery(''#', fieldId , ''').autocomplete('. - str nextPut: $[. - self options do: [:each | - str nextPutAll: '"' , each ,'"'] - separatedBy: [str nextPut: $,]. - str nextPutAll: '])'. - ^str contents - ] - - fieldContents [ - - ^[:e | - e input - id: fieldId; - value: (self value ifNil: ['']); - action: [:val | self value: val]. - e script: self completerScript] - ] -] diff --git a/iliad-stable/More/Formula/ILCheckboxField.st b/iliad-stable/More/Formula/ILCheckboxField.st deleted file mode 100644 index 9b97749..0000000 --- a/iliad-stable/More/Formula/ILCheckboxField.st +++ /dev/null @@ -1,52 +0,0 @@ -"====================================================================== -| -| Iliad.ILCheckboxField class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - - -ILField subclass: ILCheckboxField [ - - - - - fieldContents [ - - ^[:e | - e checkbox - checked: (self value ifNil: [false]); - action: [:boolean | self value: boolean]] - ] -] diff --git a/iliad-stable/More/Formula/ILCondition.st b/iliad-stable/More/Formula/ILCondition.st deleted file mode 100644 index c807d73..0000000 --- a/iliad-stable/More/Formula/ILCondition.st +++ /dev/null @@ -1,75 +0,0 @@ -"====================================================================== -| -| Iliad.ILCondition class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - - -Object subclass: ILCondition [ - | labelBlock conditionBlock | - - - - - conditionBlock [ - - ^conditionBlock - ] - - conditionBlock: aBlock [ - - conditionBlock := aBlock - ] - - labelBlock [ - - ^labelBlock - ] - - labelBlock: aBlock [ - - labelBlock := aBlock - ] - - validate: anObject [ - - ^self conditionBlock value: anObject - ] - - labelFor: anObject [ - - ^self labelBlock value: anObject - ] -] diff --git a/iliad-stable/More/Formula/ILDateInputField.st b/iliad-stable/More/Formula/ILDateInputField.st deleted file mode 100644 index a235e09..0000000 --- a/iliad-stable/More/Formula/ILDateInputField.st +++ /dev/null @@ -1,138 +0,0 @@ -"====================================================================== -| -| Iliad.ILDateInputField class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - - -ILField subclass: ILDateInputField [ - | yearsInterval | - - - - - yearsInterval [ - - ^yearsInterval ifNil: [ - (Date today year - 20) to: (Date today year + 20)] - ] - - yearsInterval: anInterval [ - - yearsInterval := anInterval - ] - - value [ - - ^super value ifNil: [Date today] - ] - - month [ - - ^self value monthIndex - ] - - month: anInteger [ - - self value: (Date - newDay: self day - monthIndex: anInteger - year: self year) - ] - - day [ - - ^self value day - ] - - day: anInteger [ - - self value: (Date - newDay: anInteger - monthIndex: self month - year: self year) - ] - - year [ - - ^self value year - ] - - year: anInteger [ - - self value: (Date - newDay: self day - monthIndex: self month - year: anInteger) - ] - - months [ - - ^1 to: 12 - ] - - days [ - - ^1 to: 31 - ] - - years [ - - ^self yearsInterval - ] - - fieldContents [ - - ^[:e | - e select build: [:select | - self months do: [:each | - select option - text: (Date nameOfMonth: each) greaseString; - action: [self month: each]; - selected: (self month = each)]]. - e select build: [:select | - self days do: [:each | - select option - text: each greaseString; - action: [self day: each]; - selected: (self day = each)]]. - e select build: [:select | - self years do: [:each | - select option - text: each greaseString; - action: [self year: each]; - selected: (self year = each)]]] - ] -] diff --git a/iliad-stable/More/Formula/ILField.st b/iliad-stable/More/Formula/ILField.st deleted file mode 100644 index adff7ba..0000000 --- a/iliad-stable/More/Formula/ILField.st +++ /dev/null @@ -1,208 +0,0 @@ -"====================================================================== -| -| Iliad.ILField class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - - -ILBuildable subclass: ILField [ - | conditions errors reader writer labelContents commentContents formula | - - - - - ILField class >> on: aFormula selector: aSelector [ - - ^self new - on: aFormula - selector: aSelector; - yourself - ] - - reader [ - - ^reader - ] - - reader: aSymbol [ - - reader := aSymbol - ] - - writer [ - - ^writer - ] - - writer: aSymbol [ - - writer := aSymbol - ] - - label: aString [ - - self labelContents: [:e | e text: aString] - ] - - labelContents: aBlock [ - - labelContents := aBlock - ] - - labelContents [ - - ^labelContents - ] - - comment: aString [ - - self commentContents: [:e | e text: aString] - ] - - commentContents: aBlock [ - - commentContents := aBlock - ] - - commentContents [ - - ^commentContents - ] - - value [ - - ^formula proxy perform: self reader - ] - - value: anObject [ - - formula proxy - perform: self writer - with: anObject - ] - - errors [ - - ^errors ifNil: [{}] - ] - - conditions [ - - ^conditions ifNil: [conditions := OrderedCollection new] - ] - - addCondition: aCondition [ - - self conditions add: aCondition - ] - - addCondition: aBlock labelled: anotherBlock [ - - self addCondition: (ILCondition new - conditionBlock: aBlock; - labelBlock: anotherBlock; - yourself) - ] - - validate [ - - errors := OrderedCollection new. - self conditions do: [:each | - (each validate: self value) ifFalse: [ - self errors add: (each labelFor: self value)]]. - ] - - build [ - - ^Iliad.ILHTMLBuilderElement new - build: self tableRowContents; - yourself - ] - - tableRowContents [ - - ^[:tbody| - tbody tr build: [:tr | - tr cssClass: 'field'. - self isValid ifFalse: [ - tr cssClass: tr cssClass, ' error']. - tr th - build: self labelContents. - tr td - build: self fieldContents]. - self commentContents ifNotNil: [ - tbody tr build: [:tr | - tr td. - tr td - cssClass: 'comment'; - build: self commentContents]]. - tbody build: self errorsContents] - ] - - fieldContents [ - - self subclassResponsibility - ] - - errorsContents [ - - ^[:tbody | - self errors notEmpty ifTrue: [ - tbody tr build: [:tr | - tr td. - tr td div - class: 'errors'; - build: [:div | - div text: self errors first]]]] - ] - - isValid [ - - ^self errors isEmpty - ] - - isMultipart [ - - ^false - ] - - on: aFormula selector: aSelector [ - - reader ifNil: [reader := aSelector]. - writer ifNil: [writer := (aSelector, ':') asSymbol]. - labelContents ifNil: [self label: aSelector greaseString]. - formula := aFormula - ] -] diff --git a/iliad-stable/More/Formula/ILFileInputField.st b/iliad-stable/More/Formula/ILFileInputField.st deleted file mode 100644 index c1f061b..0000000 --- a/iliad-stable/More/Formula/ILFileInputField.st +++ /dev/null @@ -1,72 +0,0 @@ -"====================================================================== -| -| Iliad.ILFileInputField class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - - -ILField subclass: ILFileInputField [ - - - - - fieldContents [ - - ^[:e | - (self value isNil or: [self value isString]) - ifTrue: [ - e build: self uploadContents] - ifFalse: [ - e build: self fileContents]] - ] - - uploadContents [ - - ^[:e | - e file action: [:val | self value: val]]. - ] - - fileContents [ - - ^[:e | - e text: self value filename] - ] - - - isMultipart [ - - ^true - ] -] diff --git a/iliad-stable/More/Formula/ILFormula.st b/iliad-stable/More/Formula/ILFormula.st deleted file mode 100644 index 290551f..0000000 --- a/iliad-stable/More/Formula/ILFormula.st +++ /dev/null @@ -1,341 +0,0 @@ -"====================================================================== -| -| Iliad.ILFormula class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - - -ILWidget subclass: ILFormula [ - | proxy conditions fields buttons saveAction cancelAction errors multipart | - - - - - ILFormula class >> on: anObject [ - - ^self new - setModel: anObject; - yourself - ] - - model [ - - ^proxy model - ] - - proxy [ - - ^proxy - ] - - conditions [ - - ^conditions ifNil: [conditions := OrderedCollection new] - ] - - errors [ - - ^errors ifNil: [errors := OrderedCollection new] - ] - - addCondition: aCondition [ - - self conditions add: aCondition - ] - - addCondition: aBlock labelled: anotherBlock [ - - self addCondition: (ILCondition new - conditionBlock: aBlock; - labelBlock: anotherBlock; - yourself) - ] - - fields [ - - ^fields ifNil: [fields := OrderedCollection new] - ] - - setFields: aCollection [ - - fields := aCollection - ] - - buttons [ - - ^buttons ifNil: [self defaultButtons] - ] - - buttons: aCollection [ - - buttons := aCollection - ] - - saveAction [ - - ^saveAction ifNil: [self defaultSaveAction] - ] - - saveAction: aBlock [ - - saveAction := aBlock - ] - - cancelAction [ - - ^cancelAction ifNil: [self defaultCancelAction] - ] - - cancelAction: aBlock [ - - cancelAction := aBlock - ] - - beMultipart [ - - multipart := true - ] - - multipart [ - - ^multipart ifNil: [false] - ] - - defaultButtons [ - - ^{'Save' -> #save. 'Cancel' -> #cancel} - ] - - defaultSaveAction [ - - ^[:model | self commit. self answer: self model] - ] - - defaultCancelAction [ - - ^[:model | self answer: nil] - ] - - addField: aField [ - - ^self fields add: aField - ] - - inputOn: aSelector [ - - ^self addField: (ILInputField on: self selector: aSelector) - ] - - textareaOn: aSelector [ - - ^self addField: (ILTextareaField on: self selector: aSelector) - ] - - checkboxOn: aSelector [ - - ^self addField: (ILCheckboxField on: self selector: aSelector) - ] - - passwordOn: aSelector [ - - ^self addField: (ILPasswordField on: self selector: aSelector) - ] - - dateInputOn: aSelector [ - - ^self addField: (ILDateInputField on: self selector: aSelector) - ] - - numberInputOn: aSelector [ - - ^self addField: (ILNumberInputField on: self selector: aSelector) - ] - - selectOn: aSelector [ - - ^self addField: (ILSelectField on: self selector: aSelector) - ] - - multipleCheckboxOn: aSelector [ - - ^self addField: (ILMultipleCheckboxField on: self selector: aSelector) - ] - - fileInputOn: aSelector [ - - ^self addField: (ILFileInputField on: self selector: aSelector) - ] - - autocompleteInputOn: aSelector [ - - ^self addField: (ILAutocompleteInputField on: self selector: aSelector) - ] - - do: aBlock [ - - ^self fields do: aBlock - - ] - - collect: aBlock [ - - ^self copy - setFields: (self fields collect: aBlock); - yourself - ] - - select: aBlock [ - - ^self copy - setFields: (self fields select: aBlock); - yourself - ] - - reject: aBlock [ - - ^self copy - setFields: (self fields reject: aBlock); - yourself - - ] - - scripts [ - - ^{'/javascripts/jquery.autocomplete.js'} - ] - - styles [ - - ^{'/stylesheets/jquery.autocomplete.css'} - ] - - contents [ - - ^[:e | - e div - class: 'formula'; - build: self errorsContents; - build: [:div | - div form build: [:form | - form multipart: self isMultipart. - form - div - class: 'fields'; - build: [:div2 | - div2 table tbody build: self tableContents]. - form div - class: 'buttons'; - build: self buttonsContents]]] - ] - - tableContents [ - - ^[:tbody | - self fields do: [:each | - tbody build: each]] - ] - - buttonsContents [ - - ^[:form | - self buttons do: [:each | - form button - text: each key; - action: [self perform: each value]]] - ] - - errorsContents [ - - ^[:e | - self errors notEmpty ifTrue: [ - e ul - class: 'errors'; - build: [:ul | - self errors do: [:each | - ul li text: each]]]] - ] - - save [ - - self - validate; - markDirty. - self isValid ifTrue: [ - self saveAction cull: self model] - ] - - cancel [ - - self cancelAction cull: self model - ] - - commit [ - - proxy commit - ] - - validate [ - - errors := OrderedCollection new. - self fields do: [:each | each validate]. - self isValid ifTrue: [ - self conditions do: [:each | - (each validate: self proxy) ifFalse: [ - self errors add: (each labelFor: self proxy)]]] - ] - - isEmpty [ - - ^self fields isEmpty - ] - - isValid [ - - self fields do: [:each | - each isValid ifFalse: [^false]]. - ^self errors isEmpty - ] - - isMultipart [ - - ^self multipart or: [ - (self fields select: [:each | each isMultipart]) notEmpty] - ] - - setModel: anObject [ - - proxy := ILModelProxy on: anObject - ] -] diff --git a/iliad-stable/More/Formula/ILInputField.st b/iliad-stable/More/Formula/ILInputField.st deleted file mode 100644 index 2172638..0000000 --- a/iliad-stable/More/Formula/ILInputField.st +++ /dev/null @@ -1,51 +0,0 @@ -"====================================================================== -| -| Iliad.ILInputField class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILField subclass: ILInputField [ - - - - - fieldContents [ - - ^[:e | - e input - value: (self value ifNil: ['']); - action: [:val | self value: val]] - ] -] diff --git a/iliad-stable/More/Formula/ILMultipleCheckboxField.st b/iliad-stable/More/Formula/ILMultipleCheckboxField.st deleted file mode 100644 index 55aade1..0000000 --- a/iliad-stable/More/Formula/ILMultipleCheckboxField.st +++ /dev/null @@ -1,58 +0,0 @@ -"====================================================================== -| -| Iliad.ILMultipleCheckboxField class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILOptionField subclass: ILMultipleCheckboxField [ - - - - - fieldContents [ - - ^[:e | - self options - do: [:each | - e checkbox - checked: (self value includes: each); - action: [:boolean | boolean - ifTrue: [self add: each] - ifFalse: [self remove: each]]. - e space. - e label text: (self optionLabelBlock value: each)] - separatedBy: [e br]] - ] -] diff --git a/iliad-stable/More/Formula/ILNumberInputField.st b/iliad-stable/More/Formula/ILNumberInputField.st deleted file mode 100644 index 76985be..0000000 --- a/iliad-stable/More/Formula/ILNumberInputField.st +++ /dev/null @@ -1,51 +0,0 @@ -"====================================================================== -| -| Iliad.ILNumberInputField class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILInputField subclass: ILNumberInputField [ - - - - - fieldContents [ - - ^[:e | - e input - value: (self value ifNil: [''] ifNotNil: [self value greaseString]); - action: [:val | self value: val asNumber]] - ] -] diff --git a/iliad-stable/More/Formula/ILOptionField.st b/iliad-stable/More/Formula/ILOptionField.st deleted file mode 100644 index 7c8b819..0000000 --- a/iliad-stable/More/Formula/ILOptionField.st +++ /dev/null @@ -1,106 +0,0 @@ -"====================================================================== -| -| Iliad.ILOptionField class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILField subclass: ILOptionField [ - | options optionLabelBlock | - - - - - optionLabelBlock [ - - ^optionLabelBlock ifNil: [self defaultOptionLabelBlock] - ] - - optionLabelBlock: aBlock [ - - optionLabelBlock := aBlock - ] - - defaultOptionLabelBlock [ - - ^[:option | - option isString - ifTrue: [option] - ifFalse: [option greaseString]] - ] - - options [ - - ^options ifNil: [{}] - ] - - options: aCollection [ - - options := aCollection - ] - - options: aCollection labels: aBlock [ - - self options: aCollection. - self optionLabelBlock: aBlock - ] - - value [ - - ^(super value isNil and: [self isMultiple]) - ifTrue: [OrderedCollection new] - ifFalse: [super value] - ] - - add: anObject [ - - (self value includes: anObject) ifTrue: [^self]. - self value: ((OrderedCollection withAll: self value) - add: anObject; - yourself) - ] - - remove: anObject [ - - (self value includes: anObject) ifFalse: [^self]. - self value: ((OrderedCollection withAll: self value) - remove: anObject; - yourself) - ] - - isMultiple [ - - ^true - ] -] diff --git a/iliad-stable/More/Formula/ILPasswordField.st b/iliad-stable/More/Formula/ILPasswordField.st deleted file mode 100644 index f5a91e0..0000000 --- a/iliad-stable/More/Formula/ILPasswordField.st +++ /dev/null @@ -1,52 +0,0 @@ -"====================================================================== -| -| Iliad.ILPasswordField class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - - -ILField subclass: ILPasswordField [ - - - - - fieldContents [ - - ^[:e | - e password - value: (self value ifNil: ['']); - action: [:val | self value: val]] - ] -] diff --git a/iliad-stable/More/Formula/ILSelectField.st b/iliad-stable/More/Formula/ILSelectField.st deleted file mode 100644 index 2afa002..0000000 --- a/iliad-stable/More/Formula/ILSelectField.st +++ /dev/null @@ -1,80 +0,0 @@ -"====================================================================== -| -| Iliad.ILSelectField class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - - -ILOptionField subclass: ILSelectField [ - | multiple | - - - - - multiple [ - - ^multiple ifNil: [false] - ] - - multiple: aBoolean [ - - multiple := aBoolean - ] - - isMultiple [ - - ^self multiple - ] - - fieldContents [ - - ^[:e | | val | - e select build: [:select | - val := self value. - self isMultiple ifTrue: [ - self value: OrderedCollection new. - select beMultiple]. - - self options do: [:each | - select option - selected: (self isMultiple - ifTrue: [val includes: each] - ifFalse: [self value = each]); - text: (self optionLabelBlock value: each); - action: [self isMultiple - ifFalse: [self value: each] - ifTrue: [self add: each]]]]] - ] -] diff --git a/iliad-stable/More/Formula/ILTextareaField.st b/iliad-stable/More/Formula/ILTextareaField.st deleted file mode 100644 index 387cf3f..0000000 --- a/iliad-stable/More/Formula/ILTextareaField.st +++ /dev/null @@ -1,68 +0,0 @@ -"====================================================================== -| -| Iliad.ILTextareaField class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - - -ILField subclass: ILTextareaField [ - | size | - - - - - size [ - - ^size - ] - - size: aPoint [ - - size := aPoint - ] - - fieldContents [ - - ^[:e | - e textarea build: [:textarea | - self size ifNotNil: [ - textarea - cols: self size x; - rows: self size y]. - textarea - text: (self value ifNil: ['']); - action: [:val | self value: val]]] - ] -] diff --git a/iliad-stable/More/Formula/ILTimeInputField.st b/iliad-stable/More/Formula/ILTimeInputField.st deleted file mode 100644 index 1f057ee..0000000 --- a/iliad-stable/More/Formula/ILTimeInputField.st +++ /dev/null @@ -1,128 +0,0 @@ -"====================================================================== -| -| Iliad.ILTimeInputFieldField class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - - -ILField subclass: ILTimeInputField [ - | hours minutes seconds | - - - - - initialize [ - - super initialize. - self value: Time now - ] - - hours [ - - ^hours - ] - - hours: anInteger [ - - hours := anInteger - ] - - minutes [ - - ^minutes - ] - - minutes: anInteger [ - - minutes := anInteger - ] - - seconds [ - - ^seconds - ] - - seconds: anInteger [ - - seconds := anInteger - ] - - time [ - - ^Time - hour: self hours - minute: self minutes - second: self seconds - ] - - time: aTime [ - - self hours: aTime hours. - self minutes: aTime minutes. - self seconds: aTime seconds - ] - - value: aTime [ - - super value: aTime. - self time: aTime - ] - - fieldContents [ - - ^[:e | - e select build: [:select | - (1 to: 24) do: [:each | - select option - text: each greaseString; - action: [self hours: each]; - selected: (self hours = each)]]. - e select build: [:select | - (1 to: 60) do: [:each | - select option - text: each greaseString; - action: [self minutes: each]; - selected: (self minutes = each)]]. - e select build: [:select | - (1 to: 60) do: [:each | - select option - text: each greaseString; - action: [self seconds: each]; - selected: (self seconds = each)]]. - e input beHidden - action: [:val | self value: self time]] - ] - -] diff --git a/iliad-stable/More/Formula/Public/javascripts/jquery.autocomplete.js b/iliad-stable/More/Formula/Public/javascripts/jquery.autocomplete.js deleted file mode 100644 index a945aea..0000000 --- a/iliad-stable/More/Formula/Public/javascripts/jquery.autocomplete.js +++ /dev/null @@ -1,759 +0,0 @@ -/* - * Autocomplete - jQuery plugin 1.0.2 - * - * Copyright (c) 2007 Dylan Verheul, Dan G. Switzer, Anjesh Tuladhar, Jörn Zaefferer - * - * Dual licensed under the MIT and GPL licenses: - * http://www.opensource.org/licenses/mit-license.php - * http://www.gnu.org/licenses/gpl.html - * - * Revision: $Id: jquery.autocomplete.js 5747 2008-06-25 18:30:55Z joern.zaefferer $ - * - */ - -;(function($) { - -$.fn.extend({ - autocomplete: function(urlOrData, options) { - var isUrl = typeof urlOrData == "string"; - options = $.extend({}, $.Autocompleter.defaults, { - url: isUrl ? urlOrData : null, - data: isUrl ? null : urlOrData, - delay: isUrl ? $.Autocompleter.defaults.delay : 10, - max: options && !options.scroll ? 10 : 150 - }, options); - - // if highlight is set to false, replace it with a do-nothing function - options.highlight = options.highlight || function(value) { return value; }; - - // if the formatMatch option is not specified, then use formatItem for backwards compatibility - options.formatMatch = options.formatMatch || options.formatItem; - - return this.each(function() { - new $.Autocompleter(this, options); - }); - }, - result: function(handler) { - return this.bind("result", handler); - }, - search: function(handler) { - return this.trigger("search", [handler]); - }, - flushCache: function() { - return this.trigger("flushCache"); - }, - setOptions: function(options){ - return this.trigger("setOptions", [options]); - }, - unautocomplete: function() { - return this.trigger("unautocomplete"); - } -}); - -$.Autocompleter = function(input, options) { - - var KEY = { - UP: 38, - DOWN: 40, - DEL: 46, - TAB: 9, - RETURN: 13, - ESC: 27, - COMMA: 188, - PAGEUP: 33, - PAGEDOWN: 34, - BACKSPACE: 8 - }; - - // Create $ object for input element - var $input = $(input).attr("autocomplete", "off").addClass(options.inputClass); - - var timeout; - var previousValue = ""; - var cache = $.Autocompleter.Cache(options); - var hasFocus = 0; - var lastKeyPressCode; - var config = { - mouseDownOnSelect: false - }; - var select = $.Autocompleter.Select(options, input, selectCurrent, config); - - var blockSubmit; - - // prevent form submit in opera when selecting with return key - $.browser.opera && $(input.form).bind("submit.autocomplete", function() { - if (blockSubmit) { - blockSubmit = false; - return false; - } - }); - - // only opera doesn't trigger keydown multiple times while pressed, others don't work with keypress at all - $input.bind(($.browser.opera ? "keypress" : "keydown") + ".autocomplete", function(event) { - // track last key pressed - lastKeyPressCode = event.keyCode; - switch(event.keyCode) { - - case KEY.UP: - event.preventDefault(); - if ( select.visible() ) { - select.prev(); - } else { - onChange(0, true); - } - break; - - case KEY.DOWN: - event.preventDefault(); - if ( select.visible() ) { - select.next(); - } else { - onChange(0, true); - } - break; - - case KEY.PAGEUP: - event.preventDefault(); - if ( select.visible() ) { - select.pageUp(); - } else { - onChange(0, true); - } - break; - - case KEY.PAGEDOWN: - event.preventDefault(); - if ( select.visible() ) { - select.pageDown(); - } else { - onChange(0, true); - } - break; - - // matches also semicolon - case options.multiple && $.trim(options.multipleSeparator) == "," && KEY.COMMA: - case KEY.TAB: - case KEY.RETURN: - if( selectCurrent() ) { - // stop default to prevent a form submit, Opera needs special handling - event.preventDefault(); - blockSubmit = true; - return false; - } - break; - - case KEY.ESC: - select.hide(); - break; - - default: - clearTimeout(timeout); - timeout = setTimeout(onChange, options.delay); - break; - } - }).focus(function(){ - // track whether the field has focus, we shouldn't process any - // results if the field no longer has focus - hasFocus++; - }).blur(function() { - hasFocus = 0; - if (!config.mouseDownOnSelect) { - hideResults(); - } - }).click(function() { - // show select when clicking in a focused field - if ( hasFocus++ > 1 && !select.visible() ) { - onChange(0, true); - } - }).bind("search", function() { - // TODO why not just specifying both arguments? - var fn = (arguments.length > 1) ? arguments[1] : null; - function findValueCallback(q, data) { - var result; - if( data && data.length ) { - for (var i=0; i < data.length; i++) { - if( data[i].result.toLowerCase() == q.toLowerCase() ) { - result = data[i]; - break; - } - } - } - if( typeof fn == "function" ) fn(result); - else $input.trigger("result", result && [result.data, result.value]); - } - $.each(trimWords($input.val()), function(i, value) { - request(value, findValueCallback, findValueCallback); - }); - }).bind("flushCache", function() { - cache.flush(); - }).bind("setOptions", function() { - $.extend(options, arguments[1]); - // if we've updated the data, repopulate - if ( "data" in arguments[1] ) - cache.populate(); - }).bind("unautocomplete", function() { - select.unbind(); - $input.unbind(); - $(input.form).unbind(".autocomplete"); - }); - - - function selectCurrent() { - var selected = select.selected(); - if( !selected ) - return false; - - var v = selected.result; - previousValue = v; - - if ( options.multiple ) { - var words = trimWords($input.val()); - if ( words.length > 1 ) { - v = words.slice(0, words.length - 1).join( options.multipleSeparator ) + options.multipleSeparator + v; - } - v += options.multipleSeparator; - } - - $input.val(v); - hideResultsNow(); - $input.trigger("result", [selected.data, selected.value]); - return true; - } - - function onChange(crap, skipPrevCheck) { - if( lastKeyPressCode == KEY.DEL ) { - select.hide(); - return; - } - - var currentValue = $input.val(); - - if ( !skipPrevCheck && currentValue == previousValue ) - return; - - previousValue = currentValue; - - currentValue = lastWord(currentValue); - if ( currentValue.length >= options.minChars) { - $input.addClass(options.loadingClass); - if (!options.matchCase) - currentValue = currentValue.toLowerCase(); - request(currentValue, receiveData, hideResultsNow); - } else { - stopLoading(); - select.hide(); - } - }; - - function trimWords(value) { - if ( !value ) { - return [""]; - } - var words = value.split( options.multipleSeparator ); - var result = []; - $.each(words, function(i, value) { - if ( $.trim(value) ) - result[i] = $.trim(value); - }); - return result; - } - - function lastWord(value) { - if ( !options.multiple ) - return value; - var words = trimWords(value); - return words[words.length - 1]; - } - - // fills in the input box w/the first match (assumed to be the best match) - // q: the term entered - // sValue: the first matching result - function autoFill(q, sValue){ - // autofill in the complete box w/the first match as long as the user hasn't entered in more data - // if the last user key pressed was backspace, don't autofill - if( options.autoFill && (lastWord($input.val()).toLowerCase() == q.toLowerCase()) && lastKeyPressCode != KEY.BACKSPACE ) { - // fill in the value (keep the case the user has typed) - $input.val($input.val() + sValue.substring(lastWord(previousValue).length)); - // select the portion of the value not typed by the user (so the next character will erase) - $.Autocompleter.Selection(input, previousValue.length, previousValue.length + sValue.length); - } - }; - - function hideResults() { - clearTimeout(timeout); - timeout = setTimeout(hideResultsNow, 200); - }; - - function hideResultsNow() { - var wasVisible = select.visible(); - select.hide(); - clearTimeout(timeout); - stopLoading(); - if (options.mustMatch) { - // call search and run callback - $input.search( - function (result){ - // if no value found, clear the input box - if( !result ) { - if (options.multiple) { - var words = trimWords($input.val()).slice(0, -1); - $input.val( words.join(options.multipleSeparator) + (words.length ? options.multipleSeparator : "") ); - } - else - $input.val( "" ); - } - } - ); - } - if (wasVisible) - // position cursor at end of input field - $.Autocompleter.Selection(input, input.value.length, input.value.length); - }; - - function receiveData(q, data) { - if ( data && data.length && hasFocus ) { - stopLoading(); - select.display(data, q); - autoFill(q, data[0].value); - select.show(); - } else { - hideResultsNow(); - } - }; - - function request(term, success, failure) { - if (!options.matchCase) - term = term.toLowerCase(); - var data = cache.load(term); - // recieve the cached data - if (data && data.length) { - success(term, data); - // if an AJAX url has been supplied, try loading the data now - } else if( (typeof options.url == "string") && (options.url.length > 0) ){ - - var extraParams = { - timestamp: +new Date() - }; - $.each(options.extraParams, function(key, param) { - extraParams[key] = typeof param == "function" ? param() : param; - }); - - $.ajax({ - // try to leverage ajaxQueue plugin to abort previous requests - mode: "abort", - // limit abortion to this input - port: "autocomplete" + input.name, - dataType: options.dataType, - url: options.url, - data: $.extend({ - q: lastWord(term), - limit: options.max - }, extraParams), - success: function(data) { - var parsed = options.parse && options.parse(data) || parse(data); - cache.add(term, parsed); - success(term, parsed); - } - }); - } else { - // if we have a failure, we need to empty the list -- this prevents the the [TAB] key from selecting the last successful match - select.emptyList(); - failure(term); - } - }; - - function parse(data) { - var parsed = []; - var rows = data.split("\n"); - for (var i=0; i < rows.length; i++) { - var row = $.trim(rows[i]); - if (row) { - row = row.split("|"); - parsed[parsed.length] = { - data: row, - value: row[0], - result: options.formatResult && options.formatResult(row, row[0]) || row[0] - }; - } - } - return parsed; - }; - - function stopLoading() { - $input.removeClass(options.loadingClass); - }; - -}; - -$.Autocompleter.defaults = { - inputClass: "ac_input", - resultsClass: "ac_results", - loadingClass: "ac_loading", - minChars: 1, - delay: 400, - matchCase: false, - matchSubset: true, - matchContains: false, - cacheLength: 10, - max: 100, - mustMatch: false, - extraParams: {}, - selectFirst: true, - formatItem: function(row) { return row[0]; }, - formatMatch: null, - autoFill: false, - width: 0, - multiple: false, - multipleSeparator: ", ", - highlight: function(value, term) { - return value.replace(new RegExp("(?![^&;]+;)(?!<[^<>]*)(" + term.replace(/([\^\$\(\)\[\]\{\}\*\.\+\?\|\\])/gi, "\\$1") + ")(?![^<>]*>)(?![^&;]+;)", "gi"), "$1"); - }, - scroll: true, - scrollHeight: 180 -}; - -$.Autocompleter.Cache = function(options) { - - var data = {}; - var length = 0; - - function matchSubset(s, sub) { - if (!options.matchCase) - s = s.toLowerCase(); - var i = s.indexOf(sub); - if (i == -1) return false; - return i == 0 || options.matchContains; - }; - - function add(q, value) { - if (length > options.cacheLength){ - flush(); - } - if (!data[q]){ - length++; - } - data[q] = value; - } - - function populate(){ - if( !options.data ) return false; - // track the matches - var stMatchSets = {}, - nullData = 0; - - // no url was specified, we need to adjust the cache length to make sure it fits the local data store - if( !options.url ) options.cacheLength = 1; - - // track all options for minChars = 0 - stMatchSets[""] = []; - - // loop through the array and create a lookup structure - for ( var i = 0, ol = options.data.length; i < ol; i++ ) { - var rawValue = options.data[i]; - // if rawValue is a string, make an array otherwise just reference the array - rawValue = (typeof rawValue == "string") ? [rawValue] : rawValue; - - var value = options.formatMatch(rawValue, i+1, options.data.length); - if ( value === false ) - continue; - - var firstChar = value.charAt(0).toLowerCase(); - // if no lookup array for this character exists, look it up now - if( !stMatchSets[firstChar] ) - stMatchSets[firstChar] = []; - - // if the match is a string - var row = { - value: value, - data: rawValue, - result: options.formatResult && options.formatResult(rawValue) || value - }; - - // push the current match into the set list - stMatchSets[firstChar].push(row); - - // keep track of minChars zero items - if ( nullData++ < options.max ) { - stMatchSets[""].push(row); - } - }; - - // add the data items to the cache - $.each(stMatchSets, function(i, value) { - // increase the cache size - options.cacheLength++; - // add to the cache - add(i, value); - }); - } - - // populate any existing data - setTimeout(populate, 25); - - function flush(){ - data = {}; - length = 0; - } - - return { - flush: flush, - add: add, - populate: populate, - load: function(q) { - if (!options.cacheLength || !length) - return null; - /* - * if dealing w/local data and matchContains than we must make sure - * to loop through all the data collections looking for matches - */ - if( !options.url && options.matchContains ){ - // track all matches - var csub = []; - // loop through all the data grids for matches - for( var k in data ){ - // don't search through the stMatchSets[""] (minChars: 0) cache - // this prevents duplicates - if( k.length > 0 ){ - var c = data[k]; - $.each(c, function(i, x) { - // if we've got a match, add it to the array - if (matchSubset(x.value, q)) { - csub.push(x); - } - }); - } - } - return csub; - } else - // if the exact item exists, use it - if (data[q]){ - return data[q]; - } else - if (options.matchSubset) { - for (var i = q.length - 1; i >= options.minChars; i--) { - var c = data[q.substr(0, i)]; - if (c) { - var csub = []; - $.each(c, function(i, x) { - if (matchSubset(x.value, q)) { - csub[csub.length] = x; - } - }); - return csub; - } - } - } - return null; - } - }; -}; - -$.Autocompleter.Select = function (options, input, select, config) { - var CLASSES = { - ACTIVE: "ac_over" - }; - - var listItems, - active = -1, - data, - term = "", - needsInit = true, - element, - list; - - // Create results - function init() { - if (!needsInit) - return; - element = $("
    ") - .hide() - .addClass(options.resultsClass) - .css("position", "absolute") - .appendTo(document.body); - - list = $("
      ").appendTo(element).mouseover( function(event) { - if(target(event).nodeName && target(event).nodeName.toUpperCase() == 'LI') { - active = $("li", list).removeClass(CLASSES.ACTIVE).index(target(event)); - $(target(event)).addClass(CLASSES.ACTIVE); - } - }).click(function(event) { - $(target(event)).addClass(CLASSES.ACTIVE); - select(); - // TODO provide option to avoid setting focus again after selection? useful for cleanup-on-focus - input.focus(); - return false; - }).mousedown(function() { - config.mouseDownOnSelect = true; - }).mouseup(function() { - config.mouseDownOnSelect = false; - }); - - if( options.width > 0 ) - element.css("width", options.width); - - needsInit = false; - } - - function target(event) { - var element = event.target; - while(element && element.tagName != "LI") - element = element.parentNode; - // more fun with IE, sometimes event.target is empty, just ignore it then - if(!element) - return []; - return element; - } - - function moveSelect(step) { - listItems.slice(active, active + 1).removeClass(CLASSES.ACTIVE); - movePosition(step); - var activeItem = listItems.slice(active, active + 1).addClass(CLASSES.ACTIVE); - if(options.scroll) { - var offset = 0; - listItems.slice(0, active).each(function() { - offset += this.offsetHeight; - }); - if((offset + activeItem[0].offsetHeight - list.scrollTop()) > list[0].clientHeight) { - list.scrollTop(offset + activeItem[0].offsetHeight - list.innerHeight()); - } else if(offset < list.scrollTop()) { - list.scrollTop(offset); - } - } - }; - - function movePosition(step) { - active += step; - if (active < 0) { - active = listItems.size() - 1; - } else if (active >= listItems.size()) { - active = 0; - } - } - - function limitNumberOfItems(available) { - return options.max && options.max < available - ? options.max - : available; - } - - function fillList() { - list.empty(); - var max = limitNumberOfItems(data.length); - for (var i=0; i < max; i++) { - if (!data[i]) - continue; - var formatted = options.formatItem(data[i].data, i+1, max, data[i].value, term); - if ( formatted === false ) - continue; - var li = $("
    • ").html( options.highlight(formatted, term) ).addClass(i%2 == 0 ? "ac_even" : "ac_odd").appendTo(list)[0]; - $.data(li, "ac_data", data[i]); - } - listItems = list.find("li"); - if ( options.selectFirst ) { - listItems.slice(0, 1).addClass(CLASSES.ACTIVE); - active = 0; - } - // apply bgiframe if available - if ( $.fn.bgiframe ) - list.bgiframe(); - } - - return { - display: function(d, q) { - init(); - data = d; - term = q; - fillList(); - }, - next: function() { - moveSelect(1); - }, - prev: function() { - moveSelect(-1); - }, - pageUp: function() { - if (active != 0 && active - 8 < 0) { - moveSelect( -active ); - } else { - moveSelect(-8); - } - }, - pageDown: function() { - if (active != listItems.size() - 1 && active + 8 > listItems.size()) { - moveSelect( listItems.size() - 1 - active ); - } else { - moveSelect(8); - } - }, - hide: function() { - element && element.hide(); - listItems && listItems.removeClass(CLASSES.ACTIVE); - active = -1; - }, - visible : function() { - return element && element.is(":visible"); - }, - current: function() { - return this.visible() && (listItems.filter("." + CLASSES.ACTIVE)[0] || options.selectFirst && listItems[0]); - }, - show: function() { - var offset = $(input).offset(); - element.css({ - width: typeof options.width == "string" || options.width > 0 ? options.width : $(input).width(), - top: offset.top + input.offsetHeight, - left: offset.left - }).show(); - if(options.scroll) { - list.scrollTop(0); - list.css({ - maxHeight: options.scrollHeight, - overflow: 'auto' - }); - - if($.browser.msie && typeof document.body.style.maxHeight === "undefined") { - var listHeight = 0; - listItems.each(function() { - listHeight += this.offsetHeight; - }); - var scrollbarsVisible = listHeight > options.scrollHeight; - list.css('height', scrollbarsVisible ? options.scrollHeight : listHeight ); - if (!scrollbarsVisible) { - // IE doesn't recalculate width when scrollbar disappears - listItems.width( list.width() - parseInt(listItems.css("padding-left")) - parseInt(listItems.css("padding-right")) ); - } - } - - } - }, - selected: function() { - var selected = listItems && listItems.filter("." + CLASSES.ACTIVE).removeClass(CLASSES.ACTIVE); - return selected && selected.length && $.data(selected[0], "ac_data"); - }, - emptyList: function (){ - list && list.empty(); - }, - unbind: function() { - element && element.remove(); - } - }; -}; - -$.Autocompleter.Selection = function(field, start, end) { - if( field.createTextRange ){ - var selRange = field.createTextRange(); - selRange.collapse(true); - selRange.moveStart("character", start); - selRange.moveEnd("character", end); - selRange.select(); - } else if( field.setSelectionRange ){ - field.setSelectionRange(start, end); - } else { - if( field.selectionStart ){ - field.selectionStart = start; - field.selectionEnd = end; - } - } - field.focus(); -}; - -})(jQuery); diff --git a/iliad-stable/More/Formula/Public/stylesheets/jquery.autocomplete.css b/iliad-stable/More/Formula/Public/stylesheets/jquery.autocomplete.css deleted file mode 100644 index ab47651..0000000 --- a/iliad-stable/More/Formula/Public/stylesheets/jquery.autocomplete.css +++ /dev/null @@ -1,48 +0,0 @@ -.ac_results { - padding: 0px; - background-color: white; - overflow: hidden; - z-index: 99999; -} - -.ac_results ul { - width: 100%; - list-style-position: outside; - list-style: none; - padding: 0; - margin: 0; -} - -.ac_results li { - margin: 0px; - padding: 2px 5px; - cursor: default; - display: block; - /* - if width will be 100% horizontal scrollbar will apear - when scroll mode will be used - */ - /*width: 100%;*/ - font: menu; - font-size: 12px; - /* - it is very important, if line-height not setted or setted - in relative units scroll will be broken in firefox - */ - line-height: 16px; - overflow: hidden; -} - -.ac_loading { - background: white url('indicator.gif') right center no-repeat; -} - -.ac_odd { - background-color: #eee; -} - -.ac_over { - background-color: #0088CC; - color: white; -} - diff --git a/iliad-stable/More/Formula/package.st b/iliad-stable/More/Formula/package.st deleted file mode 100644 index 4cdb8a3..0000000 --- a/iliad-stable/More/Formula/package.st +++ /dev/null @@ -1,35 +0,0 @@ -Eval [ - | builder pubDir | - builder := PackageBuilder new - name: 'Iliad-More-Formula'; - namespace: 'Iliad'; - - prereq: 'Iliad-Core'; - prereq: 'Iliad-More-UI'; - - filein: 'ILCondition.st'; - filein: 'ILField.st'; - filein: 'ILInputField.st'; - filein: 'ILNumberInputField.st'; - filein: 'ILAutocompleteInputField.st'; - filein: 'ILTextareaField.st'; - filein: 'ILPasswordField.st'; - filein: 'ILCheckboxField.st'; - filein: 'ILOptionField.st'; - filein: 'ILSelectField.st'; - filein: 'ILMultipleCheckboxField.st'; - filein: 'ILDateInputField.st'; - filein: 'ILTimeInputField.st'; - filein: 'ILFileInputField.st'; - filein: 'ILFormula.st'; - - filein: 'postLoad.st'; - yourself. - - pubDir := Directory working / 'Public'. - pubDir all do: [:each | - each isFile ifTrue: [ - builder resource: (each pathFrom: Directory working)]]. - - builder buildXml -] diff --git a/iliad-stable/More/Formula/package.xml b/iliad-stable/More/Formula/package.xml deleted file mode 100644 index 3559c82..0000000 --- a/iliad-stable/More/Formula/package.xml +++ /dev/null @@ -1,40 +0,0 @@ - - Iliad-More-Formula - Iliad - Iliad-Core - Iliad-More-UI - ILCondition.st - ILField.st - ILInputField.st - ILNumberInputField.st - ILAutocompleteInputField.st - ILTextareaField.st - ILPasswordField.st - ILCheckboxField.st - ILOptionField.st - ILSelectField.st - ILMultipleCheckboxField.st - ILDateInputField.st - ILTimeInputField.st - ILFileInputField.st - ILFormula.st - postLoad.st - ILCondition.st - ILField.st - ILInputField.st - ILNumberInputField.st - ILAutocompleteInputField.st - ILTextareaField.st - ILPasswordField.st - ILCheckboxField.st - ILOptionField.st - ILSelectField.st - ILMultipleCheckboxField.st - ILDateInputField.st - ILTimeInputField.st - ILFileInputField.st - ILFormula.st - postLoad.st - Public/stylesheets/jquery.autocomplete.css - Public/javascripts/jquery.autocomplete.js - diff --git a/iliad-stable/More/Formula/postLoad.st b/iliad-stable/More/Formula/postLoad.st deleted file mode 100644 index 9a536d1..0000000 --- a/iliad-stable/More/Formula/postLoad.st +++ /dev/null @@ -1,6 +0,0 @@ -Eval [ - ILFileHandler addDirectory: - (ILDiskDirectory new - directory: (PackageLoader packageAt: 'Iliad-More-Formula') directory / 'Public'; - yourself) -] diff --git a/iliad-stable/More/HTML5Elements/Extensions.st b/iliad-stable/More/HTML5Elements/Extensions.st deleted file mode 100644 index 6b44771..0000000 --- a/iliad-stable/More/HTML5Elements/Extensions.st +++ /dev/null @@ -1,211 +0,0 @@ -"====================================================================== -| -| HTML5 extensions -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILHTMLBuilderElement extend [ - - video [ - - ^self add: ILVideoElement new - ] - - audio [ - - ^self add: ILAudioElement new - ] - - canvas [ - - ^self add: ILCanvasElement new - ] - - command [ - - ^self add: ILCommandElement new - ] - - details [ - - ^self add: ILDetailsElement new - ] - - menu [ - - ^self add: ILMenuElement new - ] - - meter [ - - ^self add: ILMeterElement new - ] - - progress [ - - ^self add: ILProgressElement new - ] - - source [ - - ^self add: ILSourceElement new - ] - - searchInput [ - - ^self add: ILSearchInputElement new - ] - - time [ - - ^self add: ILTimeElement new - ] - - date [ - - ^self input - beDate; - yourself - ] - - datetime [ - - ^self input - beDatetime; - yourself - ] - - datetimeLocal [ - - ^self input - beDatetimeLocal; - yourself - ] - - timeInput [ - - ^self input - beTime; - yourself - ] - - range [ - - ^self input - beRange; - yourself - ] - - number [ - - ^self input - beNumber; - yourself - ] - - color [ - - ^self input - beColor; - yourself - ] - - email [ - - ^self input - beEmail; - yourself - ] - -] - - - -ILInputElement extend [ - - step: anInteger [ - - self attributeAt: 'step' put: anInteger greaseString - ] - - min: anInteger [ - - self attributeAt: 'min' put: anInteger greaseString - ] - - max: anInteger [ - - self attributeAt: 'max' put: anInteger greaseString - ] - - beDate [ - - self type: 'date' - ] - - beDatetime [ - - self type: 'datetime' - ] - - beDatetimeLocal [ - - self type: 'datetime-local' - ] - - beTime [ - - self type: 'time' - ] - - beRange [ - - self type: 'range' - ] - - beNumber [ - - self type: 'number' - ] - - beColor [ - - self type: 'color' - ] - - beEmail [ - - self type: 'email' - ] -] diff --git a/iliad-stable/More/HTML5Elements/ILAudioElement.st b/iliad-stable/More/HTML5Elements/ILAudioElement.st deleted file mode 100644 index 5a5fb46..0000000 --- a/iliad-stable/More/HTML5Elements/ILAudioElement.st +++ /dev/null @@ -1,103 +0,0 @@ -"====================================================================== -| -| Iliad.ILAudioElement class definition -| - ======================================================================" - -"====================================================================== -| Copyright (c) 2008 Berto 'd Sera for Vox Humanitatis -| X11 license (often called MIT) -| ---------------------------------------------------------------- -| Permission is hereby granted, free of charge, to any person -| obtaining a copy of this software and associated documentation -| files (the 'Software'), to deal in the Software without -| restriction, including without limitation the rights to use, -| copy, modify, merge, publish, distribute, sublicense, and/or sell -| copies of the Software, and to permit persons to whom the -| Software is furnished to do so, subject to the following -| conditions: -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES -| OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND -| NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT -| HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, -| WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING -| FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR -| OTHER DEALINGS IN THE SOFTWARE. - ======================================================================" - - - -ILHTMLBuilderElement subclass: ILAudioElement [ - - - - tag [ - - ^'audio' - ] - - autoplay [ - - self autoplay: true - ] - - controls [ - - self controls: true - ] - - preload [ - - self preloadAuto - ] - - loop [ - - self loop: true - ] - - src: aString [ - - self attributeAt: 'src' put: aString - ] - - controls: aBoolean [ - - aBoolean ifTrue: [ - self attributeAt: 'controls' put: 'controls'] - ] - - preloadNone [ - - self attributeAt: 'preload' put: 'none' - ] - - preloadMetadata [ - - self attributeAt: 'preload' put: 'metadata' - ] - - preloadAuto [ - - self attributeAt: 'preload' put: 'auto' - ] - - autoplay: aBoolean [ - - aBoolean ifTrue: [ - self attributeAt: 'autoplay' put: 'autoplay'] - ] - - loop: aBoolean [ - - aBoolean ifTrue: [ - self attributeAt: 'loop' put: 'loop'] - ] -] diff --git a/iliad-stable/More/HTML5Elements/ILCanvasElement.st b/iliad-stable/More/HTML5Elements/ILCanvasElement.st deleted file mode 100644 index 6f74046..0000000 --- a/iliad-stable/More/HTML5Elements/ILCanvasElement.st +++ /dev/null @@ -1,63 +0,0 @@ -"====================================================================== -| -| Iliad.ILCanvasElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - -ILHTMLBuilderElement subclass: ILCanvasElement [ - - - - - tag [ - - ^'canvas' - ] - - height: anInteger [ - "The height of the canvas, in CSS pixels" - - - self attributeAt: 'height' put: anInteger greaseString - ] - - width: anInteger [ - "The width of the canvas, in CSS pixels" - - - self attributeAt: 'width' put: anInteger greaseString - ] -] diff --git a/iliad-stable/More/HTML5Elements/ILCommandElement.st b/iliad-stable/More/HTML5Elements/ILCommandElement.st deleted file mode 100644 index 6e9f283..0000000 --- a/iliad-stable/More/HTML5Elements/ILCommandElement.st +++ /dev/null @@ -1,126 +0,0 @@ -"====================================================================== -| -| Iliad.ILCommandElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILHTMLBuilderElement subclass: ILCommandElement [ - - - - - tag [ - - ^'command' - ] - - beCheckbox [ - - self type: 'checkbox' - ] - - beChecked [ - - self checked: true - ] - - beCommand [ - "Specifies that its command element is a command with an associated action" - - - self type: 'command' - ] - - beDisabled [ - - self disabled: true - ] - - beHidden [ - - self hidden: true - ] - - beRadio [ - "Specifies that its command element represents a selection of one item from a list of items" - - - self type: 'radio' - ] - - checked: aBoolean [ - "Specifies that the command is selected" - - - aBoolean ifTrue: [ - self attributeAt: 'checked' put: 'checked'] - ] - - disabled: aBoolean [ - "Specifies that the command is not currently available" - - - aBoolean ifTrue: [ - self attributeAt: 'disabled' put: 'disabled'] - ] - - hidden: aBoolean [ - - aBoolean ifTrue: [ - self attributeAt: 'hidden' put: aBoolean] - ] - - icon: aString [ - "An url for an image that represents the command" - - - self attributeAt: 'icon' put: aString - ] - - label: aString [ - "The name of the command, as shown to the user" - - - self attributeAt: 'label' put: aString - ] - - type: aString [ - "Specifies that the command is not currently available" - - - self attributeAt: 'type' put: aString - ] -] diff --git a/iliad-stable/More/HTML5Elements/ILDetailsElement.st b/iliad-stable/More/HTML5Elements/ILDetailsElement.st deleted file mode 100644 index 25498d7..0000000 --- a/iliad-stable/More/HTML5Elements/ILDetailsElement.st +++ /dev/null @@ -1,57 +0,0 @@ -"====================================================================== -| -| Iliad.ILDetailsElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILHTMLBuilderElement subclass: ILDetailsElement [ - - - - - tag [ - - ^'details' - ] - - open: aBoolean [ - "Specifies that the contents of the details element should be shown to the user" - - - aBoolean ifTrue: [ - self attributeAt: 'open' put: 'open'] - ] -] diff --git a/iliad-stable/More/HTML5Elements/ILMenuElement.st b/iliad-stable/More/HTML5Elements/ILMenuElement.st deleted file mode 100644 index cfbd1e7..0000000 --- a/iliad-stable/More/HTML5Elements/ILMenuElement.st +++ /dev/null @@ -1,74 +0,0 @@ -"====================================================================== -| -| Iliad.ILMenuElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILHTMLBuilderElement subclass: ILMenuElement [ - - - - - tag [ - - ^'menu' - ] - - beToolbar [ - - self type: 'toolbar' - ] - - beContext [ - - self type: 'context' - ] - - type: aString [ - "The kind of menu being declared. - - toolbar: indicates that the element represents a tool bar. - - context: indicates that the element represents a context menu. - - If the attribute is omitted, the element represents a list of - commands that is neither a context menu or a toolbar" - - self attributeAt: 'type' put: aString - ] - - label: aString [ - "The label of the menu" - - self attributeAt: 'label' put: aString - ] -] diff --git a/iliad-stable/More/HTML5Elements/ILMeterElement.st b/iliad-stable/More/HTML5Elements/ILMeterElement.st deleted file mode 100644 index dda9589..0000000 --- a/iliad-stable/More/HTML5Elements/ILMeterElement.st +++ /dev/null @@ -1,91 +0,0 @@ -"====================================================================== -| -| Iliad.ILMeterElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILHTMLBuilderElement subclass: ILMeterElement [ - - - - - tag [ - - ^'meter' - ] - - high: anInteger [ - "The point that marks the lower boundary of the high segment of the meter" - - - self attributeAt: 'high' put: anInteger greaseString - ] - - low: anInteger [ - "The point that marks the upper boundary of the low segment of the meter" - - - self attributeAt: 'low' put: anInteger greaseString - ] - - max: anInteger [ - "The upper bound of the range for the meter" - - - self attributeAt: 'max' put: anInteger greaseString - ] - - min: anInteger [ - "The lower bound of the range for the meter" - - - self attributeAt: 'min' put: anInteger greaseString - ] - - optimum: anInteger [ - "The point that marks the optimum position for the meter" - - - self attributeAt: 'optimum' put: anInteger greaseString - ] - - value: anInteger [ - "The measured value shown by meter" - - - self attributeAt: 'value' put: anInteger greaseString - ] -] diff --git a/iliad-stable/More/HTML5Elements/ILProgressElement.st b/iliad-stable/More/HTML5Elements/ILProgressElement.st deleted file mode 100644 index 84b6361..0000000 --- a/iliad-stable/More/HTML5Elements/ILProgressElement.st +++ /dev/null @@ -1,65 +0,0 @@ -"====================================================================== -| -| Iliad.ILProgressElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILHTMLBuilderElement subclass: ILProgressElement [ - - - - - tag [ - - ^'progress' - ] - - max: anInteger [ - "Specifies how much work the task requires in total. The units are - arbitrary and not specified" - - - self attributeAt: 'max' put: anInteger greaseString - ] - - value: anInteger [ - "Specifies how much of the task has been completed. The units are - arbitrary and not specified" - - - self attributeAt: 'value' put: anInteger greaseString - ] -] - diff --git a/iliad-stable/More/HTML5Elements/ILSearchInputElement.st b/iliad-stable/More/HTML5Elements/ILSearchInputElement.st deleted file mode 100644 index 4601e44..0000000 --- a/iliad-stable/More/HTML5Elements/ILSearchInputElement.st +++ /dev/null @@ -1,56 +0,0 @@ -"====================================================================== -| -| Iliad.ILSearchInputElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILFormElementElement subclass: ILSearchInputElement [ - - - - - type [ - - ^'search' - ] - - value: aString [ - - self attributeAt: 'value' put: aString - ] -] - diff --git a/iliad-stable/More/HTML5Elements/ILSourceElement.st b/iliad-stable/More/HTML5Elements/ILSourceElement.st deleted file mode 100644 index ed95a8f..0000000 --- a/iliad-stable/More/HTML5Elements/ILSourceElement.st +++ /dev/null @@ -1,73 +0,0 @@ -"====================================================================== -| -| Iliad.ILSourceElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILHTMLBuilderElement subclass: ILSourceElement [ - - - - - tag [ - - ^'source' - ] - - media: aString [ - "The intended media type of the media source (used for helping the UA - determine, before fetching this media source, if it useful to the user)." - - - self attributeAt: 'media' put: aString - ] - - type: aString [ - "The type of the media source (used for helping the UA determine, before - fetching this media source, if it can play it)" - - - self attributeAt: 'type' put: aString - ] - - src: aString [ - "The adress of the media source" - - - self attributeAt: 'src' put: aString - ] -] - diff --git a/iliad-stable/More/HTML5Elements/ILTimeElement.st b/iliad-stable/More/HTML5Elements/ILTimeElement.st deleted file mode 100644 index 13f2d86..0000000 --- a/iliad-stable/More/HTML5Elements/ILTimeElement.st +++ /dev/null @@ -1,67 +0,0 @@ -"====================================================================== -| -| Iliad.ILTimeElement class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -ILHTMLBuilderElement subclass: ILTimeElement [ - - - - - tag [ - - ^'time' - ] - - datetime: aTime [ - "Specifies the date or time that the element represents" - - - self attributeAt: 'datetime' put: aTime - ] - - pubdate: aBoolean [ - "Indicates that the date and time given by the element is the - publication date and time of the nearest ancestor article element - or, - if the element has no ancestor article element, of the document as a - whole" - - - aBoolean ifTrue: [ - self attributeAt: 'pubdate' put: 'pubdate'] - ] -] - diff --git a/iliad-stable/More/HTML5Elements/ILVideoElement.st b/iliad-stable/More/HTML5Elements/ILVideoElement.st deleted file mode 100644 index 2a079b3..0000000 --- a/iliad-stable/More/HTML5Elements/ILVideoElement.st +++ /dev/null @@ -1,118 +0,0 @@ -"====================================================================== -| -| Iliad.ILVideoElement class definition -| - ======================================================================" - -"====================================================================== -| Copyright (c) 2008 Berto 'd Sera for Vox Humanitatis -| X11 license (often called MIT) -| ---------------------------------------------------------------- -| Permission is hereby granted, free of charge, to any person -| obtaining a copy of this software and associated documentation -| files (the 'Software'), to deal in the Software without -| restriction, including without limitation the rights to use, -| copy, modify, merge, publish, distribute, sublicense, and/or sell -| copies of the Software, and to permit persons to whom the -| Software is furnished to do so, subject to the following -| conditions: -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES -| OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND -| NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT -| HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, -| WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING -| FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR -| OTHER DEALINGS IN THE SOFTWARE. - ======================================================================" - - - -ILHTMLBuilderElement subclass: ILVideoElement [ - - - - tag [ - - ^'video' - ] - - controls [ - - self controls: true - ] - - preload [ - - self preloadAuto - ] - - autoplay [ - - self autoplay: true - ] - - loop [ - - self loop: true - ] - - height: anInteger [ - - self attributeAt: 'height' put: anInteger greaseString - ] - - width: anInteger [ - - self attributeAt: 'width' put: anInteger greaseString - ] - - src: aString [ - - self attributeAt: 'src' put: aString - ] - - controls: aBoolean [ - - aBoolean ifTrue: [ - self attributeAt: 'controls' put: 'controls'] - ] - - poster: aString [ - - self attributeAt: 'poster' put: aString - ] - - preloadNone [ - - self attributeAt: 'preload' put: 'none' - ] - - preloadMetadata [ - - self attributeAt: 'preload' put: 'metadata' - ] - - preloadAuto [ - - self attributeAt: 'preload' put: 'auto' - ] - - autoplay: aBoolean [ - - aBoolean ifTrue: [ - self attributeAt: 'autoplay' put: 'autoplay'] - ] - - loop: aBoolean [ - - aBoolean ifTrue: [ - self attributeAt: 'loop' put: 'loop'] - ] -] diff --git a/iliad-stable/More/HTML5Elements/package.st b/iliad-stable/More/HTML5Elements/package.st deleted file mode 100644 index 2834a2c..0000000 --- a/iliad-stable/More/HTML5Elements/package.st +++ /dev/null @@ -1,20 +0,0 @@ -Eval [ - PackageBuilder new - name: 'Iliad-More-HTML5Elements'; - namespace: 'Iliad'; - prereq: 'Iliad-Core'; - - filein: 'ILAudioElement.st'; - filein: 'ILCanvasElement.st'; - filein: 'ILCommandElement.st'; - filein: 'ILDetailsElement.st'; - filein: 'ILMenuElement.st'; - filein: 'ILMeterElement.st'; - filein: 'ILProgressElement.st'; - filein: 'ILSearchInputElement.st'; - filein: 'ILSourceElement.st'; - filein: 'ILTimeElement.st'; - filein: 'ILVideoElement.st'; - filein: 'Extensions.st'; - buildXml -] diff --git a/iliad-stable/More/HTML5Elements/package.xml b/iliad-stable/More/HTML5Elements/package.xml deleted file mode 100644 index a51f07e..0000000 --- a/iliad-stable/More/HTML5Elements/package.xml +++ /dev/null @@ -1,29 +0,0 @@ - - Iliad-More-HTML5Elements - Iliad - Iliad-Core - ILAudioElement.st - ILCanvasElement.st - ILCommandElement.st - ILDetailsElement.st - ILMenuElement.st - ILMeterElement.st - ILProgressElement.st - ILSearchInputElement.st - ILSourceElement.st - ILTimeElement.st - ILVideoElement.st - Extensions.st - ILAudioElement.st - ILCanvasElement.st - ILCommandElement.st - ILDetailsElement.st - ILMenuElement.st - ILMeterElement.st - ILProgressElement.st - ILSearchInputElement.st - ILSourceElement.st - ILTimeElement.st - ILVideoElement.st - Extensions.st - diff --git a/iliad-stable/More/Magritte/Builders/MATableBuilder.st b/iliad-stable/More/Magritte/Builders/MATableBuilder.st deleted file mode 100644 index b3c3c71..0000000 --- a/iliad-stable/More/Magritte/Builders/MATableBuilder.st +++ /dev/null @@ -1,96 +0,0 @@ -"====================================================================== -| -| Magritte.MATableBuilder class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Adapted from Magritte-Seaside written by Lukas Renggli -| http://source.lukas-renggli.ch/magritte. -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -MAWidgetBuilder subclass: MATableBuilder [ - - - - - buildContainerFor: aDescription [ - - ^[:e | - e - class: (self classFor: aDescription); - build: (super buildContainerFor: aDescription)] - ] - - buildControlFor: aDescription [ - - ^[:e | - e td - class: (self classFor: aDescription); - build: (super buildControlFor: aDescription)] - ] - - buildElementFor: aDescription [ - - ^[:e | - aDescription group = group - ifFalse: [self buildGroupFor: aDescription]. - e tr - build: (self buildLabelFor: aDescription); - build: (self buildControlFor: aDescription)] - ] - - buildGroupFor: aDescription [ - - ^[:e || trow | - e build: (super buildGroupFor: aDescription). - group isNil ifTrue: [^self]. - trow := e tr class: 'group'; yourself. - trow tableHeading - colSpan: 2; - text: group] - ] - - buildLabelFor: aDescription [ - - ^[:e | - e th - title: aDescription comment; - class: (self classFor: aDescription); - build: (super buildLabelFor: aDescription)] - ] - - setElement: anElement [ - element := anElement table - ] -] - diff --git a/iliad-stable/More/Magritte/Builders/MAWidgetBuilder.st b/iliad-stable/More/Magritte/Builders/MAWidgetBuilder.st deleted file mode 100644 index 7387c5a..0000000 --- a/iliad-stable/More/Magritte/Builders/MAWidgetBuilder.st +++ /dev/null @@ -1,148 +0,0 @@ -"====================================================================== -| -| Magritte.MAWidgetBuilder class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Adapted from Magritte-Seaside written by Lukas Renggli -| http://source.lukas-renggli.ch/magritte. -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -MAVisitor subclass: MAWidgetBuilder [ - | widget errors group element | - - - - - MAWidgetBuilder class >> widget: aWidget on: anElement [ - - ^self new widget: aWidget on: anElement - ] - - childAt: aDescription [ - - ^widget childAt: aDescription - ] - - classFor: aDescription [ - - | classes | - classes := OrderedCollection withAll: aDescription cssClasses. - aDescription isReadonly ifTrue: [classes add: 'readonly']. - aDescription isRequired ifTrue: [classes add: 'required']. - (self hasError: aDescription) ifTrue: [classes add: 'error']. - ^classes reduce: [:a :b | a , ' ' , b] - ] - - widget: aWidget on: anElement [ - - self - setWidget: aWidget; - setElement: anElement. - self visit: aWidget description - ] - - hasError: aDescription [ - - | current | - errors ifNotNil: [^errors includes: aDescription]. - errors := IdentitySet new. - current := widget. - [current notNil] whileTrue: [ - current isMagritteContainer ifTrue: [ - current errors do: [:each | - errors add: (each tag isDescription - ifTrue: [each tag] - ifFalse: [current description])]]. - current := current parent]. - ^self hasError: aDescription - ] - - buildContainerFor: aDescription [ - - ^[:e | - self visitAll: (aDescription select: [:each | - each isVisible and: - [each widgetClass notNil]])] - ] - - buildControlFor: aDescription [ - - ^[:e | e build: (self childAt: aDescription)] - ] - - buildElementFor: aDescription [ - - ^[:e | - aDescription group = group ifFalse: [ - self buildGroupFor: aDescription]. - e build: (self buildLabelFor: aDescription). - e build: (self buildControlFor: aDescription)] - ] - - buildGroupFor: aDescription [ - - ^[:e | group := aDescription group] - ] - - buildLabelFor: aDescription [ - - ^[:e || label | - aDescription hasLabel ifTrue: [ - label := e label. - (self childAt: aDescription) hasLabelId - ifTrue: [label for: (self childAt: aDescription) labelId]. - label text: aDescription label , ':']] - ] - - setElement: anElement [ - - element := anElement - ] - - setWidget: aWidget [ - - widget := aWidget - ] - - visitContainer: aDescription [ - - element build: (self buildContainerFor: aDescription) - ] - - visitElementDescription: aDescription [ - - element build: (self buildElementFor: aDescription) - ] -] - diff --git a/iliad-stable/More/Magritte/Decorators/MAContainerDecorator.st b/iliad-stable/More/Magritte/Decorators/MAContainerDecorator.st deleted file mode 100644 index 77a7718..0000000 --- a/iliad-stable/More/Magritte/Decorators/MAContainerDecorator.st +++ /dev/null @@ -1,88 +0,0 @@ -"====================================================================== -| -| Magritte.MAContainerDecorator class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Adapted from Magritte-Seaside written by Lukas Renggli -| http://source.lukas-renggli.ch/magritte. -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -MAWidgetDecorator subclass: MAContainerDecorator [ - - - - - buttons [ - "Answer a collection of associations. The key is either a symbol that will be performed on the decorated widget or a one-argument block that will be executed with the widget as argument. The value is the button label." - - - self subclassResponsibility - ] - - default [ - - ^self buttons first key - ] - - execute: anObject [ - - anObject isSymbol - ifFalse: [anObject value: self widget] - ifTrue: [self widget perform: anObject] - ] - - buttonsContents [ - - ^[:e || div | - div := e div - class: 'buttons'; - yourself. - self buttons do: [:each | - div button - accesskey: each value first; - action: [self execute: each key]; - text: each value]] - ] - - contents [ - - ^[:e | - e form - class: 'magritte'; - multipart: self isMultipart; - build: self decoratee contents; - build: self buttonsContents] - ] -] - diff --git a/iliad-stable/More/Magritte/Decorators/MAFormDecorator.st b/iliad-stable/More/Magritte/Decorators/MAFormDecorator.st deleted file mode 100644 index 347c18b..0000000 --- a/iliad-stable/More/Magritte/Decorators/MAFormDecorator.st +++ /dev/null @@ -1,88 +0,0 @@ -"====================================================================== -| -| Magritte.MAFormDecorator class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Adapted from Magritte-Seaside written by Lukas Renggli -| http://source.lukas-renggli.ch/magritte. -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -MAContainerDecorator subclass: MAFormDecorator [ - | buttons | - - - - - MAFormDecorator class >> buttons: aCollection [ - - ^self new - addButtons: aCollection; - yourself - ] - - addButton: aSymbol [ - - self addButton: aSymbol label: aSymbol greaseString - ] - - addButton: aSymbolOrOneArgumentBlock label: aString [ - - self buttons add: aSymbolOrOneArgumentBlock -> aString - ] - - addButtons: aCollection [ - - aCollection do: [:each | - each isVariableBinding - ifFalse: [self addButton: each] - ifTrue: [self addButton: each key label: each value]] - ] - - buttons [ - - ^buttons - ] - - buttons: aCollection [ - - buttons := aCollection - ] - - initialize [ - - super initialize. - self buttons: OrderedCollection new - ] -] - diff --git a/iliad-stable/More/Magritte/Decorators/MASwitchDecorator.st b/iliad-stable/More/Magritte/Decorators/MASwitchDecorator.st deleted file mode 100644 index ab93ecf..0000000 --- a/iliad-stable/More/Magritte/Decorators/MASwitchDecorator.st +++ /dev/null @@ -1,59 +0,0 @@ -"====================================================================== -| -| Magritte.MASwitchDecorator class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Adapted from Magritte-Seaside written by Lukas Renggli -| http://source.lukas-renggli.ch/magritte. -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -MAContainerDecorator subclass: MASwitchDecorator [ - - - - - buttons [ - - ^self widget isReadonly - ifTrue: [Array with: #edit -> 'Edit'] - ifFalse: [Array with: #save -> 'Save' with: #cancel -> 'Cancel'] - ] - - handleAnswer: anAnswer [ - - self widget readonly: true. - super handleAnswer: anAnswer - ] -] - diff --git a/iliad-stable/More/Magritte/Decorators/MAValidationDecorator.st b/iliad-stable/More/Magritte/Decorators/MAValidationDecorator.st deleted file mode 100644 index efff972..0000000 --- a/iliad-stable/More/Magritte/Decorators/MAValidationDecorator.st +++ /dev/null @@ -1,70 +0,0 @@ -"====================================================================== -| -| Magritte.MAValidationDecorator class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Adapted from Magritte-Seaside written by Lukas Renggli -| http://source.lukas-renggli.ch/magritte. -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - - -MAWidgetDecorator subclass: MAValidationDecorator [ - - - - - errors [ - - ^self widget errors - ] - - contents [ - - ^[:e | - self errors isEmpty ifFalse: [ - e build: self errorsContents]. - e build: self decoratee contents] - ] - - errorsContents [ - - ^[:e | | list | - list := e ul - class: 'errors'; - yourself. - self errors do: [:each | - list li text: each greaseString]] - ] -] - diff --git a/iliad-stable/More/Magritte/Decorators/MAWidgetDecorator.st b/iliad-stable/More/Magritte/Decorators/MAWidgetDecorator.st deleted file mode 100644 index a83792d..0000000 --- a/iliad-stable/More/Magritte/Decorators/MAWidgetDecorator.st +++ /dev/null @@ -1,51 +0,0 @@ -"====================================================================== -| -| Magritte.MAWidgetDecorator class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Adapted from Magritte-Seaside written by Lukas Renggli -| http://source.lukas-renggli.ch/magritte. -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -Iliad.ILDecorator subclass: MAWidgetDecorator [ - - - - - isMultipart [ - - ^self widget isMultipart - ] -] - diff --git a/iliad-stable/More/Magritte/Extensions.st b/iliad-stable/More/Magritte/Extensions.st deleted file mode 100644 index ef5b5cf..0000000 --- a/iliad-stable/More/Magritte/Extensions.st +++ /dev/null @@ -1,286 +0,0 @@ -"====================================================================== -| -| Magritte classes extensions -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Adapted from Magritte-Seaside written by Lukas Renggli -| http://source.lukas-renggli.ch/magritte. -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -Iliad.ILWidget extend [ - - isMagritteContainer [ - - ^false - ] -] - -Object extend [ - - asWidget [ - - ^self description asWidgetOn: self - ] -] - -MADescription extend [ - - MADescription class >> defaultCssClasses [ - - ^OrderedCollection new - ] - - MADescription class >> defaultReportColumnWidgetClass [ - - ^self defaultReportColumnWidgetClasses notEmpty - ifTrue: [self defaultReportColumnWidgetClasses first] - ] - - MADescription class >> defaultReportColumnWidgetClasses [ - - ^Array with: MADescribedColumnWidget - ] - - MADescription class >> defaultWidgetClass [ - - ^self defaultWidgetClasses notEmpty - ifTrue: [self defaultWidgetClasses first] - ifFalse: [MAUndefinedWidget] - ] - - MADescription class >> defaultWidgetClasses [ - - ^Array with: MAUndefinedWidget - ] - - MADescription class >> descriptionReportColumnWidgetClass [ - - ^MASingleOptionDescription new - accessor: #reportColumnWidgetClass; - label: 'Report Column Class'; - priority: 1010; - reference: MAClassDescription new; - options: self defaultReportColumnWidgetClasses; - default: self defaultReportColumnWidgetClass; - yourself - ] - - MADescription class >> descriptionWidgetClass [ - - ^MASingleOptionDescription new - accessor: #widgetClass; - label: 'Component Class'; - reference: MAClassDescription new; - options: self defaultWidgetClasses; - default: self defaultWidgetClass; - priority: 1000; - yourself - ] - - cssClass: aString [ - - (self propertyAt: #cssClasses ifAbsentPut: [self class defaultCssClasses]) - add: aString - ] - - cssClasses [ - - ^self propertyAt: #cssClasses ifAbsent: [self class defaultCssClasses] - ] - - cssClasses: aCollection [ - - self propertyAt: #cssClasses put: aCollection - ] - - reportColumnWidgetClass [ - - ^self propertyAt: #reportColumnWidgetClass ifAbsent: [ - self class defaultReportColumnWidgetClass] - ] - - reportColumnWidgetClass: aClass [ - - ^self propertyAt: #reportColumnWidgetClass put: aClass - ] - - widgetClass [ - - ^self - propertyAt: #widgetClass - ifAbsent: [self class defaultWidgetClass] - ] - - widgetClass: aClass [ - - ^self propertyAt: #widgetClass put: aClass - ] -] - -MAContainer extend [ - - MAContainer class >> defaultWidgetBuilder [ - - ^MATableBuilder - ] - - MAContainer class >> defaultWidgetClasses [ - - ^Array with: MAContainerWidget - ] - - asWidgetOn: anObject [ - - ^self widgetClass - memento: (anObject mementoClass - model: anObject - description: self) - ] - - widgetBuilder [ - - ^self - propertyAt: #widgetBuilder - ifAbsent: [self class defaultWidgetBuilder] - ] - - widgetBuilder: aClass [ - - self propertyAt: #widgetBuilder put: aClass - ] -] - -MABooleanDescription class extend [ - - defaultWidgetClasses [ - - ^Array with: MACheckboxWidget with: MASelectListWidget - ] -] - -MADateDescription class extend [ - - defaultWidgetClasses [ - - ^ Array with: MADateSelectorWidget - ] - - defaultWidgetClasses [ - - ^ Array with: MADateSelectorWidget - ] -] - -MAElementDescription class extend [ - - defaultWidgetClasses [ - - ^Array with: MATextInputWidget - ] -] - -MAFileDescription class extend [ - - defaultWidgetClasses [ - - ^Array with: MAFileUploadWidget - ] -] - -MAMemoDescription class extend [ - - defaultWidgetClasses [ - - ^Array with: MATextAreaWidget - ] -] - -MAMultipleOptionDescription class extend [ - - defaultWidgetClasses [ - - ^Array with: MAMultiselectListWidget with: MACheckboxGroupWidget - ] -] - -MAPasswordDescription class extend [ - - defaultWidgetClasses [ - - ^Array - with: MATextPasswordWidget - with: MAVerifiedPasswordWidget - with: MATextInputWidget - ] -] - -MASingleOptionDescription class extend [ - - defaultWidgetClasses [ - - ^Array with: MASelectListWidget - ] -] - -MATimeDescription class extend [ - - defaultWidgetClasses [ - - ^Array with: MATimeSelectorWidget - ] -] - -MATimeStampDescription class extend [ - - defaultWidgetClasses [ - - ^Array with: MATimeStampSelectorWidget - ] -] - -MAToOneRelationDescription class extend [ - - defaultWidgetClasses [ - - ^Array with: MAExternalEditorWidget with: MAInternalEditorWidget - ] -] - -MAToManyRelationDescription class extend [ - - defaultWidgetClasses [ - - ^Array with: MAOneToManyWidget - ] -] diff --git a/iliad-stable/More/Magritte/Report/MAActionColumnWidget.st b/iliad-stable/More/Magritte/Report/MAActionColumnWidget.st deleted file mode 100644 index 97b8330..0000000 --- a/iliad-stable/More/Magritte/Report/MAActionColumnWidget.st +++ /dev/null @@ -1,85 +0,0 @@ -"====================================================================== -| -| Magritte.MAActionColumnWidget class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Adapted from Magritte-Seaside written by Lukas Renggli -| http://source.lukas-renggli.ch/magritte. -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - - -MAColumnWidget subclass: MAActionColumnWidget [ - - - - - buildCellContent: anObject [ - - ^[:e | - self useLinks - ifTrue: [e build: (self buildCellLinkContent: anObject)] - ifFalse: [e build: (self buildCellFormContent: anObject)]] - ] - - buildCellFormContent: anObject [ - - self subclassResponsibility - ] - - buildCellLinkContent: anObject [ - - self subclassResponsibility - ] - - defaultTitle [ - - ^String new - ] - - defaultUseLinks [ - - ^true - ] - - useLinks [ - - ^self propertyAt: #useLinks ifAbsent: [self defaultUseLinks] - ] - - useLinks: aBoolean [ - - self propertyAt: #useLinks put: aBoolean - ] -] - diff --git a/iliad-stable/More/Magritte/Report/MACheckboxColumnWidget.st b/iliad-stable/More/Magritte/Report/MACheckboxColumnWidget.st deleted file mode 100644 index 0ba9257..0000000 --- a/iliad-stable/More/Magritte/Report/MACheckboxColumnWidget.st +++ /dev/null @@ -1,86 +0,0 @@ -"====================================================================== -| -| Magritte.MACheckboxColumnWidget class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Adapted from Magritte-Seaside written by Lukas Renggli -| http://source.lukas-renggli.ch/magritte. -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -MASelectionColumnWidget subclass: MACheckboxColumnWidget [ - - - - - buildCellFormContent: anObject [ - - ^[:e | - e checkbox - checked: (self isSelected: anObject); - action: [:value | self selectRow: anObject value: value]] - ] - - defaultSelection [ - - ^Set new - ] - - defaultStringDeselected [ - - ^self webdings: 'c' - ] - - defaultStringSelected [ - - ^self webdings: 'g' - ] - - deselectRow: anObject [ - - self selection remove: anObject ifAbsent: nil. - self report markDirty - ] - - selectRow: anObject [ - - self selection add: anObject. - self report markDirty - ] - - isSelected: anObject [ - - ^self selection includes: anObject - ] -] - diff --git a/iliad-stable/More/Magritte/Report/MAColumnWidget.st b/iliad-stable/More/Magritte/Report/MAColumnWidget.st deleted file mode 100644 index 98fb5a9..0000000 --- a/iliad-stable/More/Magritte/Report/MAColumnWidget.st +++ /dev/null @@ -1,343 +0,0 @@ -"====================================================================== -| -| Magritte.MAColumnWidget class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Adapted from Magritte-Seaside written by Lukas Renggli -| http://source.lukas-renggli.ch/magritte. -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -Object subclass: MAColumnWidget [ - | report properties | - - - - - MAColumnWidget class >> descriptionComment [ - - ^(MAStringDescription new) - accessor: #comment; - label: 'Comment'; - priority: 200; - yourself - ] - - MAColumnWidget class >> descriptionTitle [ - - ^(MAStringDescription new) - accessor: #title; - label: 'Title'; - priority: 100; - yourself - ] - - MAColumnWidget class >> new [ - - ^self basicNew initialize - ] - - buildCell: anObject index: anInteger [ - - ^[:e | - e td build: (self format - valueWithArguments: ((Array with: anObject with: anInteger) - first: self format selector numArgs))] - ] - - buildCellContent: anObject [ - - ^[:e | - e text: (self valueFor: anObject)] - ] - - buildFootCell [ - - ^[:e | - e td build: self buildFootContent] - ] - - buildFootContent [ - - ^[:e | - self footer isNil ifFalse: [ - e build: self footer]] - ] - - buildHeadCell [ - - ^[:e | - | th | - th := e th - class: self sorterStyle; - title: (self comment ifNil: ['']); - yourself. - self isSortable - ifFalse: [th build: self buildHeadContent] - ifTrue: [th a - action: [self report sort: self]; - build: self buildHeadContent]] - ] - - buildHeadContent [ - - ^[:e | - e text: self title] - ] - - cascade [ - - ^self propertyAt: #cascade ifAbsent: [self defaultCascade] - ] - - cascade: anArray [ - - self propertyAt: #cascade put: anArray - ] - - comment [ - - ^self propertyAt: #comment ifAbsent: [self defaultComment] - ] - - comment: aString [ - - self propertyAt: #comment put: aString - ] - - footer [ - - ^self propertyAt: #footer ifAbsent: [self defaultFooter] - ] - - footer: aBlock [ - - self propertyAt: #footer put: aBlock - ] - - format [ - - ^self propertyAt: #format ifAbsent: [self defaultFormat] - ] - - format: aBlock [ - - self propertyAt: #format put: aBlock - ] - - sorter [ - - ^self propertyAt: #sorter ifAbsent: [self defaultSorter] - ] - - sorter: aBlock [ - - self propertyAt: #sorter put: aBlock - ] - - title [ - - ^self propertyAt: #title ifAbsent: [self defaultTitle] - ] - - title: aString [ - - self propertyAt: #title put: aString - ] - - visible [ - - ^self propertyAt: #visible ifAbsent: [self defaultVisible] - ] - - visible: aBoolean [ - - self propertyAt: #visible put: aBoolean - ] - - column [ - - ^self report cache collect: [:each | self valueFor: each] - ] - - index [ - - ^self report columns indexOf: self - ] - - report [ - - ^report - ] - - sorterStyle [ - - ^self isSorted - ifTrue: - [self isReversed - ifTrue: [self report sorterStyles first] - ifFalse: [self report sorterStyles second]] - ifFalse: [String new] - ] - - defaultCascade [ - - ^#(#yourself) - ] - - defaultComment [ - - ^nil - ] - - defaultFooter [ - - ^nil - ] - - defaultFormat [ - - ^DirectedMessage receiver: self selector: #buildCellContent: - ] - - defaultSorter [ - - ^[:a :b | | x y | - (x := self valueFor: a) isNil - or: [(y := self valueFor: b) notNil - and: [x <= y]]] - ] - - defaultTitle [ - - ^self cascade first asCapitalizedPhrase - ] - - defaultVisible [ - - ^true - ] - - exportContent: anObject index: aNumber on: aStream [ - - aStream nextPutAll: (anObject greaseString - collect: [:each | each isSeparator ifTrue: [ - Character space] ifFalse: [each]]) - ] - - exportHeadOn: aStream [ - - self title isNil ifFalse: [aStream nextPutAll: self title] - ] - - initialize [ - - properties := Dictionary new - ] - - setReport: aReport [ - - report := aReport - ] - - isReversed [ - - ^self report sortReversed - ] - - isSortable [ - - ^self report sortEnabled and: [self sorter notNil] - ] - - isSorted [ - - ^self report sortColumn = self - ] - - isVisible [ - - ^self visible - ] - - properties [ - - ^properties - ] - - propertyAt: aSymbol [ - - ^self properties at: aSymbol - ] - - propertyAt: aSymbol ifAbsent: aBlock [ - - ^self properties at: aSymbol ifAbsent: aBlock - ] - - propertyAt: aSymbol ifAbsentPut: aBlock [ - - ^self properties at: aSymbol ifAbsentPut: aBlock - ] - - propertyAt: aSymbol put: anObject [ - - ^self properties at: aSymbol put: anObject - ] - - refresh [ - - self report markDirty - ] - - selector: aSymbol [ - - self cascade: (Array with: aSymbol) - ] - - sortRows: aCollection [ - - | result | - result := SortedCollection new: aCollection size. - result - sortBlock: self sorter; - addAll: aCollection. - ^self isReversed ifFalse: [result] ifTrue: [result reverse] - ] - - valueFor: aRow [ - - ^self cascade inject: aRow into: [:result :each | result perform: each] - ] -] - diff --git a/iliad-stable/More/Magritte/Report/MACommandColumnWidget.st b/iliad-stable/More/Magritte/Report/MACommandColumnWidget.st deleted file mode 100644 index 27f1c4c..0000000 --- a/iliad-stable/More/Magritte/Report/MACommandColumnWidget.st +++ /dev/null @@ -1,111 +0,0 @@ -"====================================================================== -| -| Magritte.MACommandColumnWidget class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Adapted from Magritte-Seaside written by Lukas Renggli -| http://source.lukas-renggli.ch/magritte. -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -MAActionColumnWidget subclass: MACommandColumnWidget [ - | commands | - - - - - addCommand: aBlock text: aString [ - - self addCommand: aBlock text: aString hash: [:val | ''] - ] - - addCommand: aBlock text: aString hash: anotherBlock [ - - self commands add: (aBlock -> anotherBlock) -> aString - ] - - addCommandOn: anObject selector: aSelector [ - - self - addCommandOn: anObject - selector: aSelector - text: aSelector allButLast asCapitalizedPhrase - ] - - addCommandOn: anObject selector: aSelector text: aString [ - - self addCommand: (DirectedMesssage receiver: anObject selector: aSelector) - text: aString - ] - - buildCellFormContent: anObject [ - - ^[:e | - self commands do: - [:each | - (e submitButton) - action: [each key key value: anObject] - hash: [each key value value: anObject]; - text: each value] - separatedBy: [e space]] - ] - - buildCellLinkContent: anObject [ - - ^[:e | - self commands - do: [:each | - e a - action: [each key key value: anObject] - hash: (each key value value: anObject); - text: each value] - separatedBy: [e space]] - ] - - commands [ - - ^commands - ] - - commands: aCollection [ - - commands := aCollection - ] - - initialize [ - - super initialize. - self commands: OrderedCollection new - ] -] - diff --git a/iliad-stable/More/Magritte/Report/MAContentsColumnWidget.st b/iliad-stable/More/Magritte/Report/MAContentsColumnWidget.st deleted file mode 100644 index 76ca55b..0000000 --- a/iliad-stable/More/Magritte/Report/MAContentsColumnWidget.st +++ /dev/null @@ -1,67 +0,0 @@ -"====================================================================== -| -| Magritte.MAContentsColumnWidget class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Adapted from Magritte-Seaside written by Lukas Renggli -| http://source.lukas-renggli.ch/magritte. -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -MAColumnWidget subclass: MAContentsColumnWidget [ - | contentsBlock | - - - - - buildCellContent: anObject [ - - ^[:e | self contentsBlock value: e value: anObject] - ] - - contentsBlock [ - - ^contentsBlock - ] - - contentsBlock: aBlock [ - - contentsBlock := aBlock - ] - - defaultTitle [ - - ^String new - ] -] - diff --git a/iliad-stable/More/Magritte/Report/MADescribedColumnWidget.st b/iliad-stable/More/Magritte/Report/MADescribedColumnWidget.st deleted file mode 100644 index 8213a99..0000000 --- a/iliad-stable/More/Magritte/Report/MADescribedColumnWidget.st +++ /dev/null @@ -1,96 +0,0 @@ -"====================================================================== -| -| Magritte.MADescribedColumnWidget class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Adapted from Magritte-Seaside written by Lukas Renggli -| http://source.lukas-renggli.ch/magritte. -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -MAColumnWidget subclass: MADescribedColumnWidget [ - | description | - - - - - buildCellContent: anObject [ - - ^[:e | - e text: (self description toString: (self valueFor: anObject))] - ] - - defaultCascade [ - - self shouldNotImplement - ] - - defaultSorter [ - - ^self description isSortable ifTrue: [super defaultSorter] - ] - - defaultTitle [ - - ^self description label - ] - - defaultVisible [ - - ^self description isVisible - ] - - description [ - - ^description - ] - - exportContent: anObject index: aNumber on: aStream [ - - super - exportContent: (self description toString: anObject) - index: aNumber - on: aStream - ] - - setDescription: aDescription [ - - description := aDescription - ] - - valueFor: aRow [ - - ^(aRow readUsing: self description) ifNil: [self description default] - ] -] - diff --git a/iliad-stable/More/Magritte/Report/MADescribedScalarColumnWidget.st b/iliad-stable/More/Magritte/Report/MADescribedScalarColumnWidget.st deleted file mode 100644 index 37f2606..0000000 --- a/iliad-stable/More/Magritte/Report/MADescribedScalarColumnWidget.st +++ /dev/null @@ -1,56 +0,0 @@ -"====================================================================== -| -| Magritte.MADescribedScalarColumnWidget class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Adapted from Magritte-Seaside written by Lukas Renggli -| http://source.lukas-renggli.ch/magritte. -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -MADescribedColumnWidget subclass: MADescribedScalarColumnWidget [ - - - - - buildCellContent: anObject [ - - ^[:e | e add: (self description reference toString: (self valueFor: anObject))] - ] - - valueFor: aRow [ - - ^aRow - ] -] - diff --git a/iliad-stable/More/Magritte/Report/MAIndexedCommandColumnWidget.st b/iliad-stable/More/Magritte/Report/MAIndexedCommandColumnWidget.st deleted file mode 100644 index 24290e5..0000000 --- a/iliad-stable/More/Magritte/Report/MAIndexedCommandColumnWidget.st +++ /dev/null @@ -1,65 +0,0 @@ -"====================================================================== -| -| Magritte.MAIndexedCommandColumnWidget class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Adapted from Magritte-Seaside written by Lukas Renggli -| http://source.lukas-renggli.ch/magritte. -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - - -MACommandColumnWidget subclass: MAIndexedCommandColumnWidget [ - - - - - buildCellContent: anObject index: anInteger [ - - ^[:e | - self commands - do: [:each | - e a - action: [each key valueWithArguments: (Array - with: anObject - with: anInteger)]; - text: each value] - separatedBy: [e space]] - ] - - defaultFormat [ - - ^DirectedMessage receiver: self selector: #renderCellContent:on:index: - ] -] - diff --git a/iliad-stable/More/Magritte/Report/MAReportWidget.st b/iliad-stable/More/Magritte/Report/MAReportWidget.st deleted file mode 100644 index 58cfef8..0000000 --- a/iliad-stable/More/Magritte/Report/MAReportWidget.st +++ /dev/null @@ -1,927 +0,0 @@ -"====================================================================== -| -| Magritte.MAReportWidget class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Adapted from Magritte-Seaside written by Lukas Renggli -| http://source.lukas-renggli.ch/magritte. -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -MAWidget subclass: MAReportWidget [ - | rows cache columns properties backtracked | - - - - - MAReportWidget class >> description2000 [ - - ^(MABooleanDescription new) - accessor: #showHeader; - label: 'Show Header'; - priority: 2000; - yourself - ] - - MAReportWidget class >> description2100 [ - - ^(MABooleanDescription new) - accessor: #showBody; - label: 'Show Body'; - priority: 2100; - yourself - ] - - MAReportWidget class >> description2200 [ - - ^(MAStringDescription new) - accessor: #tableEmpty; - label: 'Empty'; - priority: 2200; - yourself - ] - - MAReportWidget class >> description2300 [ - - ^(MABooleanDescription new) - accessor: #showFooter; - label: 'Show Footer'; - priority: 2300; - yourself - ] - - MAReportWidget class >> description2400 [ - - ^(MABooleanDescription new) - accessor: #showCaption; - label: 'Show Caption'; - priority: 2300; - yourself - ] - - MAReportWidget class >> description2500 [ - - ^(MAStringDescription new) - accessor: #tableCaption; - label: 'Caption'; - priority: 2500; - yourself - ] - - MAReportWidget class >> description2600 [ - - ^(MABooleanDescription new) - accessor: #showSummary; - label: 'Show Summary'; - priority: 2600; - yourself - ] - - MAReportWidget class >> description2700 [ - - ^(MAStringDescription new) - accessor: #tableSummary; - label: 'Summary'; - priority: 2700; - yourself - ] - - MAReportWidget class >> description4000 [ - - ^(MABooleanDescription new) - accessor: #showBatch; - label: 'Show Batch'; - priority: 4000; - yourself - ] - - MAReportWidget class >> description4100 [ - - ^(MANumberDescription new) - accessor: #batchSize; - label: 'Size'; - priority: 4100; - yourself - ] - - MAReportWidget class >> description4200 [ - - ^(MABooleanDescription new) - accessor: #showBatchFirstLast; - label: 'Show First/Last'; - priority: 4200; - yourself - ] - - MAReportWidget class >> description4300 [ - - ^(MABooleanDescription new) - accessor: #showBatchPreviousNext; - label: 'Show Previous/Next'; - priority: 4300; - yourself - ] - - MAReportWidget class >> description4400 [ - - ^(MABooleanDescription new) - accessor: #showBatchPages; - label: 'Show Pages'; - priority: 4400; - yourself - ] - - MAReportWidget class >> isAbstract [ - - ^false - ] - - MAReportWidget class >> rows: aCollection [ - - ^(self new) - rows: aCollection; - yourself - ] - - MAReportWidget class >> rows: aCollection description: aDescription [ - - | report | - report := self rows: aCollection. - aDescription asContainer do: [:each | report addColumnDescription: each]. - ^report - ] - - addColumn: aColumn [ - - columns := columns copyWith: aColumn. - ^aColumn - setReport: self; - yourself - ] - - addColumnCascade: anArray [ - - ^(self addColumn: MAColumnWidget new) - cascade: anArray; - yourself - ] - - addColumnDescription: aDescription [ - - ^self addColumn: ((aDescription reportColumnWidgetClass new) - setDescription: aDescription; - yourself) - ] - - addColumnSelector: aSelector [ - - ^(self addColumn: MAColumnWidget new) - selector: aSelector; - yourself - ] - - moveDown: aColumn [ - - | index | - index := self columns indexOf: aColumn ifAbsent: [^self]. - self columns swap: index - with: (index = self size ifFalse: [index + 1] ifTrue: [1]) - ] - - moveUp: aColumn [ - - | index | - index := self columns indexOf: aColumn ifAbsent: [^self]. - self columns swap: index - with: (index = 1 ifFalse: [index - 1] ifTrue: [self size]) - ] - - remove: aColumn [ - - columns := columns copyWithout: aColumn - ] - - batchEndIndex [ - - ^self batchPage * self batchSize min: self cache size - ] - - batchMaxPages [ - - ^(self cache size / self batchSize) ceiling - ] - - batchPageRange [ - - ^self batchPageRangeStart to: self batchPageRangeEnd - ] - - batchPageRangeEnd [ - - ^self batchMaxPages min: self batchPage + 9 - ] - - batchPageRangeStart [ - - ^self defaultBatchPage max: self batchPage - 9 - ] - - batchStartIndex [ - - ^(self batchPage - 1) * self batchSize + 1 - ] - - isOnFirstPage [ - - ^self batchPage = 1 - ] - - isOnLastPage [ - - ^self batchPage = self batchMaxPages - ] - - batchFirstContents [ - - ^ - [:e | - self isOnFirstPage - ifFalse: - [e a - action: [self batchPage: self defaultBatchPage]; - text: '|<'] - ifTrue: [e text: '|<']. - e space] - ] - - batchItemsContents [ - - ^[:e | - self batchPageRangeStart > self defaultBatchPage ifTrue: [ - e text: '...'; space]. - self batchPageRange do: [:index | - self batchPage = index - ifFalse: [e a action: [self batchPage: index]; - text: index greaseString] - ifTrue: [e span class: 'current'; - text: index greaseString]. - e space]. - self batchPageRangeEnd < (self batchMaxPages - 1) ifTrue: [ - e text: '...'; space]. - self batchPageRangeEnd = self batchMaxPages ifFalse: [ - e a - action: [self batchPage: self batchMaxPages]; - text: self batchMaxPages greaseString]] - ] - - batchLastContents [ - - ^ - [:e | - self isOnLastPage - ifFalse: [e a action: [self batchPage: self batchMaxPages]; - text: '>|'] - ifTrue: [e text: '>|']] - ] - - batchNextContents [ - - ^[:e | - self isOnLastPage - ifFalse: [e a action: [self nextPage]; text: '>>'] - ifTrue: [e text: '>>']. - e space] - ] - - batchPreviousContents [ - - ^[:e | - self isOnFirstPage - ifFalse: [e a action: [self previousPage]; text: '<<'] - ifTrue: [e text: '<<']. - e space] - ] - - batchPage [ - - ^backtracked at: #batchPage ifAbsentPut: [self defaultBatchPage] - ] - - batchPage: anInteger [ - - backtracked at: #batchPage put: anInteger. - self markDirty - ] - - batchSize [ - - ^properties at: #batchSize ifAbsent: [self defaultBatchSize] - ] - - batchSize: anInteger [ - - properties at: #batchSize put: anInteger - ] - - rowFilter [ - - ^backtracked at: #rowFilter ifAbsent: [self defaultRowFilter] - ] - - rowFilter: aBlock [ - - backtracked at: #rowFilter put: aBlock. - self refresh - ] - - rowPeriod [ - - ^properties at: #rowPeriod ifAbsent: [self defaultRowPeriod] - ] - - rowPeriod: aNumber [ - - properties at: #rowPeriod put: aNumber - ] - - rowStyles [ - - ^properties at: #rowStyles ifAbsent: [self defaultRowStyles] - ] - - rowStyles: aCollection [ - - properties at: #rowStyles put: aCollection - ] - - showBatch [ - - ^properties at: #showBatch ifAbsent: [self defaultShowBatch] - ] - - showBatch: aBoolean [ - - properties at: #showBatch put: aBoolean - ] - - showBatchFirstLast [ - - ^properties at: #showBatchFirstLast - ifAbsent: [self defaultShowBatchFirstLast] - ] - - showBatchFirstLast: aBoolean [ - - properties at: #showBatchFirstLast put: aBoolean - ] - - showBatchPages [ - - ^properties at: #showBatchPages ifAbsent: [self defaultShowBatchPages] - ] - - showBatchPages: aBoolean [ - - properties at: #showBatchPages put: aBoolean - ] - - showBatchPreviousNext [ - - ^properties at: #showBatchPreviousNext - ifAbsent: [self defaultShowBatchPreviousNext] - ] - - showBatchPreviousNext: aBoolean [ - - properties at: #showBatchPreviousNext put: aBoolean - ] - - showBody [ - - ^properties at: #showBody ifAbsent: [self defaultShowBody] - ] - - showBody: aBoolean [ - - properties at: #showBody put: aBoolean - ] - - showCaption [ - - ^properties at: #showCaption ifAbsent: [self defaultShowCaption] - ] - - showCaption: aBoolean [ - - properties at: #showCaption put: aBoolean - ] - - showFooter [ - - ^properties at: #showFooter ifAbsent: [self defaultShowFooter] - ] - - showFooter: aBoolean [ - - properties at: #showFooter put: aBoolean - ] - - showHeader [ - - ^properties at: #showHeader ifAbsent: [self defaultShowHeader] - ] - - showHeader: aBoolean [ - - properties at: #showHeader put: aBoolean - ] - - showSummary [ - - ^properties at: #showSummary ifAbsent: [self defaultShowSummary] - ] - - showSummary: aBoolean [ - - properties at: #showSummary put: aBoolean - ] - - sortColumn [ - - ^backtracked at: #sortColumn ifAbsent: [self defaultSortColumn] - ] - - sortColumn: aColumn [ - - backtracked at: #sortColumn put: aColumn - ] - - sortEnabled [ - - ^properties at: #sortEnabled ifAbsent: [self defaultSortEnabled] - ] - - sortEnabled: aBoolean [ - - properties at: #sortEnabled put: aBoolean - ] - - sortReversed [ - - ^backtracked at: #sortReversed ifAbsent: [self defaultSortReversed] - ] - - sortReversed: aBoolean [ - - backtracked at: #sortReversed put: aBoolean - ] - - sorterStyles [ - - ^properties at: #sorterStyles ifAbsent: [self defaultSorterStyles] - ] - - sorterStyles: aCollection [ - - properties at: #sorterStyles put: aCollection - ] - - tableCaption [ - - ^properties at: #tableCaption ifAbsent: [self defaultTableCaption] - ] - - tableCaption: aString [ - - properties at: #tableCaption put: aString - ] - - tableEmpty [ - - ^properties at: #tableEmpty ifAbsent: [self defaultTableEmpty] - ] - - tableEmpty: aString [ - - properties at: #tableEmpty put: aString - ] - - tableSummary [ - - ^properties at: #tableSummary ifAbsent: [self defaultTableSummary] - ] - - tableSummary: aString [ - - properties at: #tableSummary put: aString - ] - - cache [ - "Return the cached rows of the receiver, these rows are filtered and sorted." - - - cache isNil - ifTrue: [self cache: (self sortRows: (self filterRows: self rows asArray))]. - ^cache - ] - - cache: aCollection [ - - cache := aCollection - ] - - columns [ - - ^columns - ] - - columns: aCollection [ - - columns := aCollection - ] - - states [ - - ^Array with: backtracked - ] - - visible [ - - ^self showBatch - ifFalse: [self cache] - ifTrue: [self cache copyFrom: self batchStartIndex to: self batchEndIndex] - ] - - visibleColumns [ - - ^self columns select: [:each | each isVisible] - ] - - contents [ - - ^ - [:e | - (e table) - class: 'report'; - build: self tableContents] - ] - - tableContents [ - - ^[:e || thead tfoot tbody | - self showCaption ifTrue: [ - e build: self tableCaptionContents]. - self showSummary ifTrue: [ - e build: self tableSummaryContents]. - thead := e thead. - self showHeader ifTrue: [ - thead build: self tableHeadContents]. - ((self showBatch - and: [self hasMoreThanOnePage]) - or: [self showFooter]) ifTrue: - ["we must not produce an empty tfoot element, this is not valid xhtml" - tfoot := e tfoot. - self showFooter ifTrue: [ - tfoot build: self tableFootContents]. - self showBatch ifTrue: [ - tfoot build: self tableBatchContents]]. - tbody := e tbody. - self showBody ifTrue: [ - tbody build: self tableBodyContents]] - ] - - defaultBatchPage [ - - ^1 - ] - - defaultBatchSize [ - - ^10 - ] - - defaultRowFilter [ - - ^nil - ] - - defaultRowPeriod [ - - ^1 - ] - - defaultRowStyles [ - - ^Array with: 'odd' with: 'even' - ] - - defaultShowBatch [ - - ^true - ] - - defaultShowBatchFirstLast [ - - ^false - ] - - defaultShowBatchPages [ - - ^true - ] - - defaultShowBatchPreviousNext [ - - ^true - ] - - defaultShowBody [ - - ^true - ] - - defaultShowCaption [ - - ^false - ] - - defaultShowFooter [ - - ^false - ] - - defaultShowHeader [ - - ^true - ] - - defaultShowSummary [ - - ^false - ] - - defaultSortColumn [ - - ^nil - ] - - defaultSortEnabled [ - - ^true - ] - - defaultSortReversed [ - - ^false - ] - - defaultSorterStyles [ - - ^Array with: 'ascending' with: 'descending' - ] - - defaultTableCaption [ - - ^nil - ] - - defaultTableEmpty [ - - ^'The report is empty.' - ] - - defaultTableSummary [ - - ^nil - ] - - export [ - - ^String streamContents: [:stream | self exportOn: stream] - ] - - exportBodyOn: aStream [ - - self cache withIndexDo: [:row :index | - self visibleColumns do: [:column | - column - exportContent: (column valueFor: row) - index: index - on: aStream] - separatedBy: [aStream tab]. - aStream cr] - ] - - exportHeaderOn: aStream [ - - self visibleColumns do: [:each | each exportHeadOn: aStream] - separatedBy: [aStream tab]. - aStream cr - ] - - exportOn: aStream [ - - self showHeader ifTrue: [self exportHeaderOn: aStream]. - self showBody ifTrue: [self exportBodyOn: aStream] - ] - - filterRows: aCollection [ - - ^self hasRowFilter - ifFalse: [aCollection] - ifTrue: [aCollection select: self rowFilter] - ] - - rowStyleForNumber: aNumber [ - - ^self rowStyles - at: (aNumber - 1) // self rowPeriod \\ self rowStyles size + 1 - ifAbsent: [String new] - ] - - sortRows: aCollection [ - - ^self isSorted - ifFalse: [aCollection] - ifTrue: [self sortColumn sortRows: aCollection] - ] - - hasMoreThanOnePage [ - - ^self batchSize < self cache size - ] - - hasRowFilter [ - - ^self rowFilter notNil - ] - - isSorted [ - - ^self sortColumn notNil - ] - - initialize [ - - super initialize. - rows := columns := Array new. - properties := Dictionary new. - backtracked := Dictionary new - ] - - nextPage [ - - self isOnLastPage - ifFalse: - [self batchPage: self batchPage + 1. - self markDirty] - ] - - previousPage [ - - self isOnFirstPage - ifFalse: - [self batchPage: self batchPage - 1. - self markDirty] - ] - - refresh [ - - self - cache: nil; - batchPage: self defaultBatchPage. - self columns do: [:each | each refresh]. - self markDirty - ] - - sort: aColumn [ - - aColumn = self sortColumn - ifTrue: - [self sortReversed - ifFalse: [self sortReversed: true] - ifTrue: - [self - sortColumn: nil; - sortReversed: false]] - ifFalse: - [self - sortColumn: aColumn; - sortReversed: false]. - self refresh - ] - - rows [ - "Return the rows of the receiver." - - - ^rows - ] - - rows: aCollection [ - "Set the rows of the receiver." - - - rows := aCollection. - self refresh - ] - - tableBatchContents [ - - ^[:e | - self hasMoreThanOnePage ifTrue: [| td | - td := e tr td - class: 'batch'; - colspan: self visibleColumns size; - yourself. - self showBatchFirstLast - ifTrue: [td build: self batchFirstContents]. - self showBatchPreviousNext - ifTrue: [td build: self batchPreviousContents]. - self showBatchPages - ifTrue: [td build: self batchItemsContents]. - self showBatchPreviousNext - ifTrue: [td build: self batchNextContents]. - self showBatchFirstLast - ifTrue: [td build: self batchLastContents]]] - ] - - tableBodyContents [ - - ^[:e | - self visible isEmpty - ifTrue: [| tr | - tr := e tr - class: 'empty'; - yourself. - tr td - colspan: self visibleColumns size; - text: self tableEmpty] - ifFalse: [| tr | - self visible keysAndValuesDo: [:index :row | - tr := e tr - class: (self rowStyleForNumber: index); - yourself. - self visibleColumns do: [:col | - tr build: (col - buildCell: row - index: index)]]]] - ] - - tableCaptionContents [ - - ^[:e | (e text tag: 'caption') add: self tableCaption] - ] - - tableFootContents [ - - ^[:e | | tr | - tr := e tr. - self visibleColumns do: [:each | - tr build: each buildFootCell]] - ] - - tableHeadContents [ - - ^[:e | | tr | - tr := e tr. - self visibleColumns do: [:each | - tr build: each buildHeadCell]] - ] - - tableSummaryContents [ - - ^[:e | (e text tag: 'summary') text: self tableSummary] - ] -] - diff --git a/iliad-stable/More/Magritte/Report/MASelectionColumnWidget.st b/iliad-stable/More/Magritte/Report/MASelectionColumnWidget.st deleted file mode 100644 index e03078d..0000000 --- a/iliad-stable/More/Magritte/Report/MASelectionColumnWidget.st +++ /dev/null @@ -1,142 +0,0 @@ -"====================================================================== -| -| Magritte.MASelectionColumnWidget class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Adapted from Magritte-Seaside written by Lukas Renggli -| http://source.lukas-renggli.ch/magritte. -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -MAActionColumnWidget subclass: MASelectionColumnWidget [ - | selection | - - - - - buildCellLinkContent: anObject [ - - | selected | - selected := self isSelected: anObject. - ^[:e | - e a - class: (selected isNil ifFalse: ['selected']); - action: [self selectRow: anObject value: selected not]; - build: (selected - ifTrue: [self stringSelected] - ifFalse: [self stringDeselected])] - ] - - defaultSelection [ - - self subclassResponsibility - ] - - defaultStringDeselected [ - - self subclassResponsibility - ] - - defaultStringSelected [ - - self subclassResponsibility - ] - - deselectRow: anObject [ - - self subclassResponsibility - ] - - refresh [ - - super refresh. - self selection: self defaultSelection - ] - - selectRow: anObject [ - - self subclassResponsibility - ] - - selectRow: anObject value: aBoolean [ - - aBoolean - ifTrue: [self selectRow: anObject] - ifFalse: [self deselectRow: anObject] - ] - - isSelected: anObject [ - - self subclassResponsibility - ] - - selection [ - - selection isNil ifTrue: [self selection: self defaultSelection]. - ^selection - ] - - selection: anObject [ - - selection := anObject - ] - - stringDeselected [ - - ^self propertyAt: #stringDeselected - ifAbsent: [self defaultStringDeselected] - ] - - stringDeselected: aString [ - - ^self propertyAt: #stringDeselected put: aString - ] - - stringSelected [ - - ^self propertyAt: #stringSelected ifAbsent: [self defaultStringSelected] - ] - - stringSelected: aString [ - - ^self propertyAt: #stringSelected put: aString - ] - - webdings: aString [ - - ^[:e | e span - style: 'font-family: Webdings'; - text: aString] - ] -] - diff --git a/iliad-stable/More/Magritte/Report/MAToggleColumnWidget.st b/iliad-stable/More/Magritte/Report/MAToggleColumnWidget.st deleted file mode 100644 index 3000e44..0000000 --- a/iliad-stable/More/Magritte/Report/MAToggleColumnWidget.st +++ /dev/null @@ -1,56 +0,0 @@ -"====================================================================== -| -| Magritte.MAToggleColumnWidget class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Adapted from Magritte-Seaside written by Lukas Renggli -| http://source.lukas-renggli.ch/magritte. -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -MADescribedColumnWidget subclass: MAToggleColumnWidget [ - - - - - buildCellContent: anObject [ - - | value | - value := self valueFor: anObject. - ^[:e | - e a - action: [anObject write: value not using: self description]; - text: (self description toString: value)] - ] -] - diff --git a/iliad-stable/More/Magritte/Widgets/MACheckboxGroupWidget.st b/iliad-stable/More/Magritte/Widgets/MACheckboxGroupWidget.st deleted file mode 100644 index 20e75aa..0000000 --- a/iliad-stable/More/Magritte/Widgets/MACheckboxGroupWidget.st +++ /dev/null @@ -1,100 +0,0 @@ -"====================================================================== -| -| Magritte.MACheckboxGroupWidget class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Adapted from Magritte-Seaside written by Lukas Renggli -| http://source.lukas-renggli.ch/magritte. -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -MAMultipleSelectionWidget subclass: MACheckboxGroupWidget [ - - - - - MACheckboxGroupWidget class >> isAbstract [ - - ^false - ] - - editorContents [ - - ^[:e | - e input - beHidden - action: [self clear]. - self optionsWithIndexDo: [:each :index | - | optionId | - optionId := self optionId: index. - e checkbox - id: optionId; - checked: (self selectedList includes: each); - action: [:val | val - ifTrue: [self add: each] - ifFalse: [self remove: each]]. - e space. - e label - for: optionId; - text: (self labelForOption: each)] - separatedBy: [e br]] - ] - - hasLabelId [ - - ^self isReadonly - ] - - isDistinct [ - - ^true - ] - - optionId: anInteger [ - - ^self id: 'option' , anInteger greaseString - ] - - optionsWithIndexDo: elementAndIndexBlock separatedBy: separatorBlock [ - - | index | - index := 1. - self description allOptions do: - [:each | - elementAndIndexBlock value: each value: index. - index := index + 1] - separatedBy: separatorBlock - ] -] - diff --git a/iliad-stable/More/Magritte/Widgets/MACheckboxWidget.st b/iliad-stable/More/Magritte/Widgets/MACheckboxWidget.st deleted file mode 100644 index c3ef560..0000000 --- a/iliad-stable/More/Magritte/Widgets/MACheckboxWidget.st +++ /dev/null @@ -1,71 +0,0 @@ -"====================================================================== -| -| Magritte.MACheckboxWidget class definition -| - ======================================================================" - -"====================================================================== -| -| copyright (c) 2008-2010 -| nicolas petton , -| sébastien audier -| -| adapted from magritte-seaside written by lukas renggli -| http://source.lukas-renggli.ch/magritte. -| -| this file is part of the iliad framework. -| -| permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'software'), to deal in the software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the software, and to -| permit persons to whom the software is furnished to do so, subject to -| the following conditions: -| -| the above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the software. -| -| the software is provided 'as is', without warranty of any kind, -| express or implied, including but not limited to the warranties of -| merchantability, fitness for a particular purpose and noninfringement. -| in no event shall the authors or copyright holders be liable for any -| claim, damages or other liability, whether in an action of contract, -| tort or otherwise, arising from, out of or in connection with the -| software or the use or other dealings in the software. -| - ======================================================================" - - - -MAElementWidget subclass: MACheckboxWidget [ - - - - - MACheckboxWidget class >> isAbstract [ - - ^false - ] - - editorContents [ - - ^[:e | - | label | - label := e label. - (label checkbox) - id: self labelId; - disabled: self isReadonly; - action: [:val | self value: val]; - checked: self value = true. - e - space; - text: self description label] - ] - - hasLabelId [ - - ^true - ] -] - diff --git a/iliad-stable/More/Magritte/Widgets/MAContainerWidget.st b/iliad-stable/More/Magritte/Widgets/MAContainerWidget.st deleted file mode 100644 index df5887d..0000000 --- a/iliad-stable/More/Magritte/Widgets/MAContainerWidget.st +++ /dev/null @@ -1,239 +0,0 @@ -"====================================================================== -| -| Magritte.MAContainerWidget class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Adapted from Magritte-Seaside written by Lukas Renggli -| http://source.lukas-renggli.ch/magritte. -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - - -MADescriptionWidget subclass: MAContainerWidget [ - | errors children readonly | - - - - - MAContainerWidget class >> isAbstract [ - - ^false - ] - - addForm [ - - self addForm: #(#save #cancel) - ] - - addForm: aCollection [ - - self decorateWith: (MAFormDecorator buttons: aCollection) - ] - - addSwitch [ - - self decorateWith: MASwitchDecorator new. - self readonly: true - ] - - addValidatedForm [ - - self - addForm; - addValidation - ] - - addValidatedForm: aCollection [ - - self - addForm: aCollection; - addValidation - ] - - addValidatedSwitch [ - - self - addSwitch; - addValidation - ] - - addValidation [ - - self decorateWith: MAValidationDecorator new - ] - - buildChildren [ - - ^self description inject: Dictionary new - into: - [:result :each | - each isVisible - ifTrue: - [result at: each - put: (each widgetClass - memento: self memento - description: each - parent: self)]. - result] - ] - - doValidate [ - - self memento validate. - self children do: [:each | each doValidate] - ] - - withContainersDo: aBlock [ - "This does a depth first search through all children and - evaluates a block for all container widgets that have their - own memento." - - - self withContainersDo: aBlock in: self - ] - - withContainersDo: aBlock in: aWidget [ - "This does a depth first search through all children and - evaluates a block for all container widgets that have their - own memento." - - - aWidget children do: [:each | self withContainersDo: aBlock in: each]. - aWidget isMagritteContainer ifTrue: [aBlock value: aWidget] - ] - - cancel [ - - self - reset; - answer: nil - ] - - commit [ - - self - withContainersDo: [:each | each memento commit]; - markDirty - ] - - edit [ - - self readonly: false. - self markDirty - ] - - reset [ - - self withContainersDo: [:each | each memento reset]. - self markDirty - ] - - save [ - - self validate ifFalse: [^self markDirty]. - self - commit; - answer: self model - ] - - validate [ - - errors := OrderedCollection new. - [self withContainersDo: [:each | each doValidate]] on: MAError - do: - [:error | - errors add: error. - error isResumable ifTrue: [error resume]]. - ^errors isEmpty - ] - - childAt: aDescription [ - - ^children at: aDescription ifAbsent: [nil] - ] - - children [ - - ^children values - ] - - errors [ - "Answer a collection of exceptions, the list of standing errors." - - - ^errors - ] - - contents [ - - ^[:e | self description widgetBuilder widget: self on: e] - ] - - initialize [ - - super initialize. - errors := OrderedCollection new - ] - - setChildren: aDictionary [ - - children := aDictionary - ] - - setDescription: aDescription [ - - super setDescription: aDescription. - self setChildren: self buildChildren - ] - - isMagritteContainer [ - - ^true - ] - - isReadonly [ - - ^super isReadonly or: [self readonly] - ] - - readonly [ - - ^readonly ifNil: [readonly := false] - ] - - readonly: aBoolean [ - - readonly := aBoolean - ] -] - diff --git a/iliad-stable/More/Magritte/Widgets/MADateSelectorWidget.st b/iliad-stable/More/Magritte/Widgets/MADateSelectorWidget.st deleted file mode 100644 index 812e108..0000000 --- a/iliad-stable/More/Magritte/Widgets/MADateSelectorWidget.st +++ /dev/null @@ -1,66 +0,0 @@ -"====================================================================== -| -| Magritte.MADateSelectorWidget class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Adapted from Magritte-Seaside written by Lukas Renggli -| http://source.lukas-renggli.ch/magritte. -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -MATextInputWidget subclass: MADateSelectorWidget [ - - - - - buttonsContents [ - - ^[:e | - (e button) - text: 'choose'; - action: [self choose]] - ] - - choose [ - - | selector | - selector := DateSelector new. - selector - selectedDate: ((self value notNil and: [ - self description isSatisfiedBy: self value]) - ifFalse: [Date current] - ifTrue: [self value]). - self chooser: selector - ] -] - diff --git a/iliad-stable/More/Magritte/Widgets/MADescriptionWidget.st b/iliad-stable/More/Magritte/Widgets/MADescriptionWidget.st deleted file mode 100644 index 661c378..0000000 --- a/iliad-stable/More/Magritte/Widgets/MADescriptionWidget.st +++ /dev/null @@ -1,137 +0,0 @@ -"====================================================================== -| -| Magritte.MADescriptionWidget class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Adapted from Magritte-Seaside written by Lukas Renggli -| http://source.lukas-renggli.ch/magritte. -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -MAWidget subclass: MADescriptionWidget [ - | description memento parent | - - - - - MADescriptionWidget class >> memento: aMemento [ - - ^self memento: aMemento description: aMemento description - ] - - MADescriptionWidget class >> memento: aMemento description: aDescription [ - - ^self - memento: aMemento - description: aDescription - parent: nil - ] - - MADescriptionWidget class >> memento: aMemento description: aDescription parent: aComponent [ - - ^(self new) - setMemento: aMemento; - setDescription: aDescription; - setParent: aComponent; - yourself - ] - - description [ - - ^description - ] - - labelId [ - - ^self id , 'label' - ] - - memento [ - - ^memento - ] - - parent [ - - ^parent - ] - - doValidate [ - "Enables widgets to raise errors when the model is validated." - - - - ] - - id [ - - ^self class name asLowercase , self hash greaseString - ] - - model [ - - ^self memento model - ] - - root [ - - ^self isRoot ifTrue: [self] ifFalse: [self parent root] - ] - - isReadonly [ - - ^self description isReadonly - or: [self isRoot not and: [self parent isReadonly]] - ] - - isRoot [ - - ^self parent isNil - ] - - setDescription: aDescription [ - - description := aDescription - ] - - setMemento: aMemento [ - - memento := aMemento - ] - - setParent: aComponent [ - - parent := aComponent - ] -] - diff --git a/iliad-stable/More/Magritte/Widgets/MAElementWidget.st b/iliad-stable/More/Magritte/Widgets/MAElementWidget.st deleted file mode 100644 index 426662d..0000000 --- a/iliad-stable/More/Magritte/Widgets/MAElementWidget.st +++ /dev/null @@ -1,120 +0,0 @@ -"====================================================================== -| -| Magritte.MAElementWidget class definition -| - ======================================================================" - -"====================================================================== -| -| Copyright (c) 2008-2010 -| Nicolas Petton , -| Sébastien Audier -| -| Adapted from Magritte-Seaside written by Lukas Renggli -| http://source.lukas-renggli.ch/magritte. -| -| This file is part of the Iliad framework. -| -| Permission is hereby granted, free of charge, to any person obtaining -| a copy of this software and associated documentation files (the -| 'Software'), to deal in the Software without restriction, including -| without limitation the rights to use, copy, modify, merge, publish, -| distribute, sublicense, and/or sell copies of the Software, and to -| permit persons to whom the Software is furnished to do so, subject to -| the following conditions: -| -| The above copyright notice and this permission notice shall be -| included in all copies or substantial portions of the Software. -| -| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, -| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -| - ======================================================================" - - - -MADescriptionWidget subclass: MAElementWidget [ - - - - - contents [ - - ^[:e | - self isReadonly - ifTrue: [e build: self viewerContents] - ifFalse: [e build: self editorContents]] - ] - - editorContents [ - - ^self viewerContents - ] - - viewerContents [ - - ^[:e | - e text: self string] - ] - - hasLabelId [ - "Return whether somewhere an element is rendered with - the id ==labelId== that can be reference by a