TestCase subclass: SoapActionTestCase [ testIntent [ | act | act := SoapAction intent: 'urn:targetObjectURI:fooBar'. self should: [act printString = ('SOAPAction: ' , '"urn:targetObjectURI:fooBar"' , (String with: Character cr with: Character lf))] ] testIntentByRequestURI [ | act | act := SoapAction intentByRequestURI. self should: [act printString = ('SOAPAction: ' , '""' , (String with: Character cr with: Character lf))] ] testNoIntent [ | act | act := SoapAction noIntent. self should: [act printString = ('SOAPAction: ' , (String with: Character cr with: Character lf))] ] ] TestCase subclass: SoapDecoderTestCase [ arrayOfArrayXML [ ^' 17974494715439249409 aV34fTn/QoILMlilPla2Pw== 20030913T14:26:28 +200 ' ] arrayReturnEnvelopeDocumentStyleXML [ ^' US 379 CA 376 ' ] arrayWithEmptyStringXML [ ^' Hello Dolphin ' ] complexDataXML [ "Google API like complex XML" ^' false 1 0.194871 2k somehost snippet... true http://www.squeak.org Squeak home page 1 1 true squeak ' ] dotNetSharedValuesEnvelopeXML [ ^' 22039 22933 23177 23249 23393 ' ] dotNetSharedValuesEnvelopeXML2 [ ^' Ume 36 1970-11-22T00:00:00.0000000-07:00 Ramon 31 1995-11-22T00:00:00.0000000-07:00 ' ] dotNetSharedValuesEnvelopeXML3 [ ^' 42 632900993212352500 632900993212508750 1 2 3 ' ] multiReturnEnvelopeDocumentStyleXML [ ^' 5 65413 Brno-Chrlice Brno-msto 1 65384 Liberec Chrastava ' ] oneSizeArrayReturnEnvelopeDocumentStyleXML [ ^' US 379 ' ] sharedValuesXML [ ^' My Life and Work Henry Ford
mailto:henryford@hotmail.com http://www.henryford.com ' ] singleReturnEnvelopeDocumentStyleXML [ ^' bareString ' ] testDecodeAnyArray [ | dec ret | dec := SoapDecoder new. ret := dec decodeXmlElement: (SoapVariable name: 'anyArr1' value: #(1 '2' 3.0)) asXmlElement. self should: [ret = #(1 '2' 3.0)] ] testDecodeArrayOfArray [ | dec arrayElem ret | dec := SoapDecoder new. arrayElem := SoapWrapElement fromXml: self arrayOfArrayXML. ret := dec decodeXmlElement: arrayElem. self should: [(ret at: 'Array') isKindOf: Array]. self should: [((ret at: 'Array') at: 1) = #()]. self should: [((ret at: 'Array') at: 2) = #(17974494715439249409 'aV34fTn/QoILMlilPla2Pw==' '20030913T14:26:28 +200')] ] testDecodeArrayReturnEnvelopeDocumentStyleXML [ "self debug: #testDecodeArrayReturnEnvelopeDocumentStyleXML" | envelopeBuilder returnEnvelope message resp value dict1 dict2 | SoapDecoder arrayTypeDict at: 'DataVersionArrayElement' put: Array. envelopeBuilder := SoapEnvelopeBuilder new. returnEnvelope := envelopeBuilder buildSoapEnvelopeFromXmlString: self arrayReturnEnvelopeDocumentStyleXML. message := SoapMessage envelope: returnEnvelope. resp := SoapResponse fromSoapMessage: message. resp style: #document. value := resp returnValue. SoapDecoder arrayTypeDict removeKey: 'DataVersionArrayElement'. self should: [value size = 2]. dict1 := value first. self should: [(dict1 at: 'build') = '379']. self should: [(dict1 at: 'country') = 'US']. dict2 := value second. self should: [(dict2 at: 'build') = '376']. self should: [(dict2 at: 'country') = 'CA'] ] testDecodeArrayWithEmptyString [ | dec arrayElem ret | dec := SoapDecoder new. arrayElem := SoapWrapElement fromXml: self arrayWithEmptyStringXML. ret := dec decodeXmlElement: arrayElem. self should: [(ret at: 'anArray') isKindOf: Array]. self should: [((ret at: 'anArray') at: 2) = ''] ] testDecodeBase64Binary [ | dec ret bytes | dec := SoapDecoder new. bytes := ByteArray with: 1 with: 2 with: 3 with: 4. ret := dec decodeXmlElement: (SoapVariable name: 'binbin' value: bytes type: #ByteArray) asXmlElement. self should: [ret = bytes] ] testDecodeBoolean [ "self debug: #testDecodeBoolean" | dec ret | dec := SoapDecoder new. ret := dec decodeXmlElement: (SoapVariable name: 'arg1' value: 'true' type: #Boolean) asXmlElement. self should: [ret = true]. ret := dec decodeXmlElement: (SoapVariable name: 'arg1' value: '1' type: #Boolean) asXmlElement. self should: [ret = true]. ret := dec decodeXmlElement: (SoapVariable name: 'arg1' value: 'false' type: #Boolean) asXmlElement. self should: [ret = false]. ret := dec decodeXmlElement: (SoapVariable name: 'arg1' value: '0' type: #Boolean) asXmlElement. self should: [ret = false] ] testDecodeComplexData [ "self debug: #testDecodeComplexData" | dec complexElem ret resultElements resultElement directoryCategory | dec := SoapDecoder new. complexElem := SoapWrapElement fromXml: self complexDataXML. ret := dec decodeXmlElement: complexElem. self should: [ret isKindOf: Dictionary]. self should: [(ret at: 'startIndex') = 1]. self should: [(ret at: 'searchTime') = 0.194871]. self should: [(ret at: 'searchQuery') = 'squeak']. resultElements := ret at: 'resultElements'. self should: [resultElements isKindOf: Array]. self should: [resultElements size = 1]. resultElement := resultElements first. self should: [resultElement isKindOf: Dictionary]. self should: [(resultElement at: 'URL') = 'http://www.squeak.org']. self should: [(resultElement at: 'title') = 'Squeak home page']. directoryCategory := resultElement at: 'directoryCategory'. self should: [directoryCategory isKindOf: Dictionary]. self should: [(directoryCategory at: 'fullViewableName') = ''] ] testDecodeDotNetSharedValuesXMLEnvelope [ "self debug: #testDecodeDotNetSharedValuesXMLEnvelope" | originalUseDotNetStyleSharedValues envelopeBuilder returnEnvelope message resp value | [originalUseDotNetStyleSharedValues := SoapResponse useDotNetStyleSharedValues. SoapResponse useDotNetStyleSharedValues: true. envelopeBuilder := SoapEnvelopeBuilder new. returnEnvelope := envelopeBuilder buildSoapEnvelopeFromXmlString: self dotNetSharedValuesEnvelopeXML. message := SoapMessage envelope: returnEnvelope. resp := SoapResponse fromSoapMessage: message. value := resp returnValue. self should: [value = #(22039 22933 23177 23249 23393 nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)]] ensure: [SoapResponse useDotNetStyleSharedValues: originalUseDotNetStyleSharedValues] ] " testDecodeDotNetSharedValuesXMLEnvelope2 [ | originalUseDotNetStyleSharedValues envelopeBuilder returnEnvelope message resp value | self should: [(Smalltalk at: #SoapSampleCustomer ifAbsent: []) ~= nil] SoapSampleCustomer initialize. [originalUseDotNetStyleSharedValues := SoapResponse useDotNetStyleSharedValues. SoapResponse useDotNetStyleSharedValues: true. envelopeBuilder := SoapEnvelopeBuilder new. returnEnvelope := envelopeBuilder buildSoapEnvelopeFromXmlString: self dotNetSharedValuesEnvelopeXML2. message := SoapMessage envelope: returnEnvelope. resp := SoapResponse fromSoapMessage: message. value := resp returnValue. self should: [value size = 2]. self should: [value first name = 'Ume']. self should: [value first age = 36]. self should: [value first dateOfBirth = (DateAndTime fromString: '1970-11-22T00:00:00-07:00')]. self should: [value second name = 'Ramon']. self should: [value second age = 31]. self should: [value second dateOfBirth = (DateAndTime fromString: '1995-11-22T00:00:00-07:00')]] ensure: [SoapResponse useDotNetStyleSharedValues: originalUseDotNetStyleSharedValues] ] " testDecodeDotNetSharedValuesXMLEnvelope3 [ "self debug: #testDecodeDotNetSharedValuesXMLEnvelope3" | originalUseDotNetStyleSharedValues envelopeBuilder returnEnvelope message resp value outparams | [originalUseDotNetStyleSharedValues := SoapResponse useDotNetStyleSharedValues. SoapResponse useDotNetStyleSharedValues: true. envelopeBuilder := SoapEnvelopeBuilder new. returnEnvelope := envelopeBuilder buildSoapEnvelopeFromXmlString: self dotNetSharedValuesEnvelopeXML3. message := SoapMessage envelope: returnEnvelope. resp := SoapResponse fromSoapMessage: message. value := resp returnValue. self should: [value size = 10]. self should: [value first = '632900993212352500']. self should: [value second = '632900993212508750']. outparams := resp outparameters. self should: [outparams size = 2]. self should: [outparams first = 42]. self should: [outparams second = #(1 2 3)]] ensure: [SoapResponse useDotNetStyleSharedValues: originalUseDotNetStyleSharedValues] ] testDecodeEmptyString [ | dec ret | dec := SoapDecoder new. ret := dec decodeXmlElement: (SoapVariable name: 'arg1' value: '' type: #String) asXmlElement. self should: [ret = ''] ] testDecodeFloatArray [ | dec ret | dec := SoapDecoder new. ret := dec decodeXmlElement: (SoapVariable name: 'floatArr1' value: #(1.1 2.2 3.3000000000000003)) asXmlElement. self should: [ret = #(1.1 2.2 3.3000000000000003)] ] testDecodeInteger [ | dec ret | dec := SoapDecoder new. ret := dec decodeXmlElement: (SoapVariable name: 'arg1' value: '1234567' type: #Integer) asXmlElement. self should: [ret = 1234567] ] testDecodeIntegerArray [ | dec ret | dec := SoapDecoder new. ret := dec decodeXmlElement: (SoapVariable name: 'intArr1' value: #(1 2 3) type: #Array) asXmlElement. self should: [ret = #(1 2 3)] ] testDecodeIsSafe [ ] testDecodeMultiReturnEnvelopeDocumentStyleXML [ "self debug: #testDecodeMultiReturnEnvelopeDocumentStyleXML" | envelopeBuilder returnEnvelope message resp value dict1 dict2 | envelopeBuilder := SoapEnvelopeBuilder new. returnEnvelope := envelopeBuilder buildSoapEnvelopeFromXmlString: self multiReturnEnvelopeDocumentStyleXML. message := SoapMessage envelope: returnEnvelope. resp := SoapResponse fromSoapMessage: message. resp style: #document. value := resp returnValue. self should: [value size = 2]. dict1 := value first. self should: [(dict1 at: 'id') = '5']. self should: [(dict1 at: 'number') = '65413']. self should: [(dict1 at: 'address1') = 'Brno-Chrlice']. self should: [(dict1 at: 'address2') = 'Brno-msto']. dict2 := value second. self should: [(dict2 at: 'id') = '1']. self should: [(dict2 at: 'number') = '65384']. self should: [(dict2 at: 'address1') = 'Liberec']. self should: [(dict2 at: 'address2') = 'Chrastava'] ] testDecodeNil [ "self debug: #testDecodeNil" | originalUseNull dec ret | [originalUseNull := SoapEncoder useXsiNullAttribute. dec := SoapDecoder new. SoapEncoder useXsiNullAttribute: true. ret := dec decodeXmlElement: (SoapWrapElement fromXml: ''). self should: [ret = nil]] ensure: [SoapEncoder useXsiNullAttribute: originalUseNull] ] testDecodeOneSizeArrayReturnEnvelopeDocumentStyleXML [ "self debug: #testDecodeOneSizeArrayReturnEnvelopeDocumentStyleXML" | envelopeBuilder returnEnvelope message resp value dict1 | SoapDecoder arrayTypeDict at: 'DataVersionArrayElement' put: Array. envelopeBuilder := SoapEnvelopeBuilder new. returnEnvelope := envelopeBuilder buildSoapEnvelopeFromXmlString: self oneSizeArrayReturnEnvelopeDocumentStyleXML. message := SoapMessage envelope: returnEnvelope. resp := SoapResponse fromSoapMessage: message. resp style: #document. value := resp returnValue. SoapDecoder arrayTypeDict removeKey: 'DataVersionArrayElement'. self should: [value size = 1]. dict1 := value first. self should: [(dict1 at: 'build') = '379']. self should: [(dict1 at: 'country') = 'US'] ] testDecodeSharedValues [ "self debug: #testDecodeSharedValues" | xml elem dec address book person | xml := SoapDecoderTestCase new sharedValuesXML. elem := SoapWrapElement fromXml: xml. dec := SoapDecoder new. elem := dec decodeXmlElement: elem. address := elem at: 'Address'. book := elem at: 'Book'. person := elem at: 'Person'. self should: [(book at: 'author') = person]. self should: [(person at: 'address') = address] ] testDecodeSingleReturnEnvelopeDocumentStyleXML [ "self debug: #testDecodeSingleReturnEnvelopeDocumentStyleXML" | envelopeBuilder returnEnvelope message resp value | envelopeBuilder := SoapEnvelopeBuilder new. returnEnvelope := envelopeBuilder buildSoapEnvelopeFromXmlString: self singleReturnEnvelopeDocumentStyleXML. message := SoapMessage envelope: returnEnvelope. resp := SoapResponse fromSoapMessage: message. resp style: #document. value := resp returnValue. self should: [value = 'bareString'] ] testDecodeString [ | dec ret | dec := SoapDecoder new. ret := dec decodeXmlElement: (SoapVariable name: 'arg1' value: 'Smalltalk' type: #String) asXmlElement. self should: [ret = 'Smalltalk'] ] testDecodeStringArray [ | dec ret | dec := SoapDecoder new. ret := dec decodeXmlElement: (SoapVariable name: 'stringArr1' value: #('a' 'b' '') type: #Array) asXmlElement. self should: [ret = #('a' 'b' '')] ] testDefaultTypesDecodeIsSafe [ "self debug: #testDefaultTypesDecodeIsSafe" | classes | classes := SoapDecoder typeDict values asSet collect: [:each | Smalltalk at: each]. classes do: [:each | | inst | inst := [Integer readFrom: '1+2*3'] on: Error do: [:ex | ex "Handled"]. (each isKindOf: Number) ifTrue: [self assert: (inst = 0 or: [inst isKindOf: Error])] ifFalse: [self assert: ((inst isKindOf: each) or: [inst isKindOf: Error])]. self deny: inst = 9] ] ] TestCase subclass: SoapBodyTestCase [ testAddBodyEntries [ | body ent1 ent2 | body := SoapBody new. ent1 := SoapWrapElement named: 'request1' withPrefix: 'm1'. ent1 declareNamespace: 'm1' uri: 'urn:request:1'. body addBodyEntry: ent1. ent2 := SoapWrapElement named: 'request1' withPrefix: 'm2'. ent2 declareNamespace: 'm2' uri: 'urn:request:2'. body addBodyEntry: ent2. self should: [ent1 parent = body]. self should: [ent2 parent = body]. self should: [(body bodyEntries at: 1) = ent1]. self should: [(body bodyEntries at: 2) = ent2] ] testIsMustUnderstandEnabled [ | body | body := SoapBody new. self should: [body isMustUnderstandEnabled] ] testOverrideEncodingStyle [ | env body ent1 | env := SoapEnvelope new. env declareSoapEncEncoding. self should: [(env getAttributeNamed: SoapConstants soapEnvPrefix , ':' , SoapConstants encodingStyle) = SoapConstants soapEncURI]. self should: [env encodingStyleURIs = (Array with: SoapConstants soapEncURI)]. body := env addBody. body declareNamespace: 'b' uri: 'urn:body:1'. body declareEncodingIn: 'b' uri: 'urn:encoding:1'. self shouldnt: [body encodingStyleURIs = (Array with: SoapConstants soapEncURI)]. self should: [body encodingStyleURIs = (Array with: 'urn:encoding:1')]. ent1 := SoapWrapElement named: 'request1' withPrefix: 'm1'. ent1 declareNamespace: 'm1' uri: 'urn:request:1'. body declareEncodingIn: 'm1' uri: 'urn:encoding:2'. body addBodyEntry: ent1. self should: [ent1 encodingStyleURIs = (Array with: 'urn:encoding:2')] ] ] TestCase subclass: SoapEncArrayTestCase [ testArrayItemType [ | elem1 elem2 | elem1 := (SoapVariable name: 'arr' value: #(1 2 3)) asXmlElement. self should: [elem1 arrayItemType = (SoapConstants xsdPrefixColon , 'integer')]. elem2 := (SoapVariable name: 'arr' value: #(1 'two' 3)) asXmlElement. self should: [elem2 arrayItemType = (SoapConstants xsdPrefixColon , 'anyType')] ] testArraySize [ | elem1 elem2 | elem1 := (SoapVariable name: 'arr' value: #(1 nil 3)) asXmlElement. self should: [elem1 size = 3]. elem2 := (SoapVariable name: 'arr' value: #()) asXmlElement. self should: [elem2 size = 0] ] testArrayWithNamespace [ | elem1 | elem1 := (SoapVariable name: 'arr' value: #(1 2 3) xsdType: 'ns1:myArrayType' namespace: 'http://my.com/nm') asXmlElement. self should: [(elem1 declaredNamespaceURIFor: 'ns1') = 'http://my.com/nm'] ] testIsArrayType [ | elem1 elem2 | elem1 := (SoapVariable name: 'arr' value: #(1 2 3)) asXmlElement. self should: [elem1 isArrayType]. elem2 := (SoapVariable name: 'prim' value: 1) asXmlElement. self shouldnt: [elem2 isArrayType] ] ] TestCase subclass: SoapEnvelopeTestCase [ testEnvelopeMustUnderstand [ | env | env := SoapEnvelope new. self should: [env body isMustUnderstandEnabled]. env addHeader. env header disableMustUnderstand. self shouldnt: [env body isMustUnderstandEnabled] ] testEnvelopeTypicalEncodingStyle [ | env body | env := SoapEnvelope new. env declareSoapEncEncoding. self should: [(env getAttributeNamed: SoapConstants soapEnvPrefix , ':' , SoapConstants encodingStyle) = SoapConstants soapEncURI]. self should: [env encodingStyleURIs = (Array with: SoapConstants soapEncURI)]. body := env addBody. self should: [body encodingStyleURIs = (Array with: SoapConstants soapEncURI)] ] ] TestCase subclass: SoapExceptionBuilderTestCase [ fooBarBazFault [ | soapFault details stErrorClass messageText detail | soapFault := SoapFault new. details := SoapWrapElement named: 'details' withPrefix: 'e'. stErrorClass := details createChildNamed: 'ErrorClass'. stErrorClass value: 'FooBarBaz'. messageText := details createChildNamed: 'messageText'. messageText value: 'invalid not existing class'. detail := soapFault addDetail. detail addSubElement: details. ^soapFault ] messageNotUnderstoodFault [ ^[nil add: 1] on: MessageNotUnderstood do: [:ex | | soapFault soapFaultDetailBuilder | soapFault := SoapFault new. soapFaultDetailBuilder := SoapFaultDetailBuilder new. soapFaultDetailBuilder buildSoapFaultDetailOn: soapFault from: ex. ex return: soapFault] ] testMessageNotUnderstoodSignal [ | fault builder exception | fault := self messageNotUnderstoodFault. builder := SoapExceptionBuilder new. exception := builder buildExceptionFrom: fault. self should: [exception tag = '<>']. self should: [exception messageText = 'did not understand #add:']. self should: [exception signal] raise: MessageNotUnderstood ] testNotExistErrorClassSignal [ | fault builder | fault := self fooBarBazFault. builder := SoapExceptionBuilder new. self should: [builder buildExceptionFrom: fault] raise: SoapNoSuchExceptionClass ] testZeroDivideSignal [ | fault builder exception | fault := self zeroDivideFault. builder := SoapExceptionBuilder new. exception := builder buildExceptionFrom: fault. self should: [exception signal] raise: ZeroDivide ] zeroDivideFault [ ^[1 / 0] on: ZeroDivide do: [:ex | | soapFault soapFaultDetailBuilder | soapFault := SoapFault new. soapFaultDetailBuilder := SoapFaultDetailBuilder new. soapFaultDetailBuilder buildSoapFaultDetailOn: soapFault from: ex. ex return: soapFault] ] ] TestCase subclass: SoapFaultTestCase [ testBasicFault [ | fault detail | fault := SoapFault client faultstring: 'Client Error!'. self should: [fault faultcode = (SoapConstants soapEnvPrefixColon , SoapConstants client)]. self should: [fault faultstring = 'Client Error!']. detail := fault addDetail. self should: [detail name = 'detail'] ] testDetailedFault [ | fault detail myErrors myErrors2 message errorcode | fault := SoapFault client faultstring: 'Client Error!'. detail := fault addDetail. myErrors := detail addSubElement: (SoapWrapElement named: 'myErrors' withPrefix: 'e'). myErrors declareNamespace: 'e' uri: 'http://www.mars.dti.ne.jp/~umejava/smalltalk/SoapOpera/errors'. (myErrors createChildNamed: 'message') value: 'My application didn''t work'. (myErrors createChildNamed: 'errorcode') value: '1001'. myErrors2 := fault detail findSubElementNamed: 'e:myErrors'. "##Apparently more work needed##" message := myErrors2 children at: 1. errorcode := myErrors2 children at: 2. self should: [message value = 'My application didn''t work']. self should: [errorcode value = '1001'] ] testMinorFaultCodes [ "##OBSOLETE## hierarchical notation is no longer used in SOAP1.2" | fault | fault := SoapFault client faultstring: 'Client Error!'. fault attachMinorFaultCodes: #('Authentication' 'Password' 'Expired'). self should: [fault faultcode = (SoapConstants soapEnvPrefixColon , 'Client.Authentication.Password.Expired')] ] ] TestCase subclass: SoapHeaderTestCase [ testMustUnderstand [ | header | header := SoapHeader new. self shouldnt: [header isMustUnderstandEnabled]. header enableMustUnderstand. self should: [header isMustUnderstandEnabled]. header disableMustUnderstand. self shouldnt: [header isMustUnderstandEnabled] ] ] TestCase subclass: SoapNullDecoderTestCase [ testDecodeBoolean [ | dec ret | dec := SoapNullDecoder new. ret := dec decodeXmlElement: ((SoapVariable name: 'arg1' value: true) encoding: #nullEncoding; asXmlElement). self should: [ret = true] ] testDecodeInteger [ | dec ret | dec := SoapNullDecoder new. ret := dec decodeXmlElement: ((SoapVariable name: 'arg1' value: 1234567) encoding: #nullEncoding; asXmlElement). self should: [ret = 1234567] ] testDecodeObject [ | dec ret dict | dec := SoapNullDecoder new. dict := Dictionary new. dict at: #Smalltalk put: #Cool. dict at: #Java put: #Plain. ret := dec decodeXmlElement: ((SoapVariable name: 'arg1' value: dict) encoding: #nullEncoding; asXmlElement). self should: [ret = dict] ] testDecodeString [ | dec ret | dec := SoapNullDecoder new. ret := dec decodeXmlElement: ((SoapVariable name: 'arg1' value: 'Smalltalk') encoding: #nullEncoding; asXmlElement). self should: [ret = 'Smalltalk'] ] ] TestCase subclass: SoapNullEncoderTestCase [ testEncodingInteger [ | enc ret | enc := SoapNullEncoder new. ret := enc encodeSoapVariable: (SoapVariable name: 'auau' value: 1). self should: [(ret getAttributeNamed: 'xsi:type') = 'Null-ENC:SmallInteger']. self should: [ret value = 1]. ret := enc encodeSoapVariable: (SoapVariable name: 'auau' value: 10000000000 type: #Integer). self should: [(ret getAttributeNamed: 'xsi:type') = 'Null-ENC:LargePositiveInteger']. self should: [ret value = 10000000000] ] testEncodingNil [ | enc ret | enc := SoapNullEncoder new. ret := enc encodeSoapVariable: (SoapVariable name: 'auau' value: nil). self should: [ret name = 'auau']. self should: [(ret getAttributeNamed: 'xsi:type') = 'Null-ENC:UndefinedObject']. self should: [ret value isNil] ] testEncodingObject [ | enc obj ret | enc := SoapNullEncoder new. obj := #(1 2 #(#hello 'Smalltalk') 3). ret := enc encodeSoapVariable: (SoapVariable name: 'auau' value: obj). self should: [ret name = 'auau']. self should: [(ret getAttributeNamed: 'xsi:type') = 'Null-ENC:Array']. self should: [ret value = obj] ] testEncodingString [ | enc ret | enc := SoapNullEncoder new. ret := enc encodeSoapVariable: (SoapVariable name: 'auau' value: 'smalltalk'). self should: [(ret getAttributeNamed: 'xsi:type') = 'Null-ENC:String']. self should: [ret value = 'smalltalk']. ret := enc encodeSoapVariable: (SoapVariable name: 'auau' value: 'ruby' type: #String). self should: [(ret getAttributeNamed: 'xsi:type') = 'Null-ENC:String']. self should: [ret value = 'ruby'] ] ] TestCase subclass: SoapVariableTestCase [ testAsXmlElementSimple [ | inst elem | inst := SoapVariable name: 'foo' value: 1 type: #Integer. elem := inst asXmlElement. self should: [elem name = 'foo']. self should: [elem parent = nil]. self should: [(elem getAttributeNamed: 'xsi:type') = 'xsd:integer']. self should: [(elem getAttributeNamed: 'env:encodingStyle') = SoapConstants soapEncURI] ] " testAsXmlElementSimpleSq [ | inst elem | inst := SoapVariable name: 'foo' value: 1 type: #Integer. inst encoding: #soapSqEncoding. elem := inst asXmlElement. self should: [elem name = 'foo']. self should: [elem parent = nil]. self should: [(elem getAttributeNamed: 'xsi:type') = 'xsd:integer']. self should: [(elem getAttributeNamed: 'env:encodingStyle') = SoapConstants soapSqEncURI] ] " ] TestCase subclass: SoapWrapElementTestCase [ echoString [ "From ROUND 2 SOAP Interoperability Tests Specification" "http://www.whitemesa.com/interop/proposal2.html#echoString" ^' hello world ' ] testFromXmlElement [ | sdom elem body callElem argElem | sdom := SoXmlUtil parseXml: self echoString. elem := SoapWrapElement fromXmlElement: sdom. self should: [elem name = 'SOAP-ENV:Envelope']. self should: [(elem getAttributeNamed: 'SOAP-ENV:encodingStyle') = 'http://schemas.xmlsoap.org/soap/encoding/']. "The XML parser does not add the namespace attributes... self should: [(elem getAttributeNamed: 'xmlns:SOAP-ENC') = 'http://schemas.xmlsoap.org/soap/encoding/']. self should: [(elem getAttributeNamed: 'xmlns:SOAP-ENV') = 'http://schemas.xmlsoap.org/soap/envelope/']. self should: [(elem getAttributeNamed: 'xmlns:xsd') = 'http://www.w3.org/2001/XMLSchema']. self should: [(elem getAttributeNamed: 'xmlns:xsi') = 'http://www.w3.org/2001/XMLSchema-instance']. " body := elem children first. self should: [body name = 'SOAP-ENV:Body']. callElem := body children first. self should: [callElem name = 'm:echoString']. " self should: [(callElem getAttributeNamed: 'xmlns:m') = 'http://soapinterop.org/']. " argElem := callElem children first. self should: [argElem name = 'inputString']. self should: [argElem value = 'hello world'] "elem inspect." ] ] TestCase subclass: SoapEncStructTestCase [ testEncodeBookStruct [ "self debug: #testEncodeBookStruct" | struct1 elem1 children struct2 elem2 elem3 | struct1 := SoapEncStruct fromAssociations: {#author -> 'Henry Ford'. #preface -> 'Prefatory text'. #intro -> 'This is a book.'}. elem1 := (SoapVariable name: 'e:Book' value: struct1) asXmlElement. self should: [elem1 name = 'e:Book']. self should: [elem1 size = 3]. children := elem1 children. self should: [children first name asSymbol = #author]. self should: [children first value = 'Henry Ford']. self should: [children second name asSymbol = #preface]. self should: [children second value = 'Prefatory text']. self should: [children third name asSymbol = #intro]. self should: [children third value = 'This is a book.']. struct2 := SoapEncStruct fromAssociations: {#author -> 'Henry Ford'. #preface -> 'Prefatory text'. #intro -> 'This is a book.'} named: nil. elem2 := (SoapVariable name: 'e:Book' value: struct2) asXmlElement. self should: [elem2 name = 'e:Book']. self should: [elem2 size = 3]. children := elem2 children. self should: [children first name asSymbol = #author]. self should: [children first value = 'Henry Ford']. self should: [children second name asSymbol = #preface]. self should: [children second value = 'Prefatory text']. self should: [children third name asSymbol = #intro]. self should: [children third value = 'This is a book.']. elem3 := (SoapVariable name: 'e:Book' value: struct2 xsdType: nil namespace: 'http://auau.com') asXmlElement. self should: [elem3 name = 'e:Book']. self should: [elem3 size = 3]. self should: [elem3 declaredNamespacePrefixes includes: 'e']. self should: [(elem3 declaredNamespaceURIFor: 'e') = 'http://auau.com']. children := elem3 children. self should: [children first name asSymbol = #author]. self should: [children first value = 'Henry Ford']. self should: [children second name asSymbol = #preface]. self should: [children second value = 'Prefatory text']. self should: [children third name asSymbol = #intro]. self should: [children third value = 'This is a book.']. ] testEncodeEmbeddedBookStruct [ "self debug: #testEncodeEmbeddedBookStruct" | address person book elem1 | address := SoapEncStruct fromAssociations: {#email -> 'mailto:henryford@hotmail.com'. #web -> 'http://www.henryford.com'}. person := SoapEncStruct fromAssociations: {#name -> 'My Life and Work'. #address -> address} named: 'e:Person'. book := SoapEncStruct fromAssociations: {#title -> 'My Life and Work'. #author -> person} named: 'e:Book'. elem1 := (SoapVariable name: 'e:Book' value: book) asXmlElement. self should: [elem1 name = 'e:Book']. self should: [elem1 children size = 2]. person := elem1 findChildNamed: 'author'. self should: [person name = 'author']. self should: [person children size = 2]. address := person findChildNamed: 'address'. self should: [address name = 'address']. self should: [address children size = 2]. self should: [address firstChild value = 'mailto:henryford@hotmail.com'] ] testEncodeSharedBookStruct [ "self debug: #testEncodeSharedBookStruct" | address person1 person2 book1 enc elem1 auther initials | address := SoapEncStruct fromAssociations: {#email -> 'mailto:henryford@hotmail.com'. #web -> 'http://www.henryford.com'} named: 'e:Address'. person1 := SoapEncStruct fromAssociations: {#name -> 'Henry Ford'. #address -> address} named: 'e:Person'. person2 := SoapEncStruct fromAssociations: {#name -> 'hf'. #address -> address} named: 'e:Initials'. book1 := SoapEncStruct fromAssociations: {#title -> 'My Life and Work'. #author -> person1. #initials -> person2} named: 'e:Book'. enc := SoapEncoder new useSharedValues: true. elem1 := enc encodeSoapVariable: (SoapVariable name: 'e:Book' value: book1). auther := elem1 findChildNamed: 'author'. initials := elem1 findChildNamed: 'initials'. self should: [(auther findChildNamed: 'address') id = ((initials findChildNamed: 'address') href copyFrom: 2) asNumber] ] ] TestCase subclass: SoapEncoderTestCase [ testEncodeBase64Binary [ "self debug: #testEncodeBase64Binary" | enc ret bytes | enc := SoapEncoder new. bytes := ByteArray with: 1 with: 2 with: 3 with: 4. ret := enc encodeSoapVariable: (SoapVariable name: 'binbin' value: bytes). self should: [(ret getAttributeNamed: 'xsi:type') = 'xsd:base64Binary']. self should: [ret value = 'AQIDBA=='] ] testEncodeBoolean [ | enc ret | enc := SoapEncoder new. ret := enc encodeSoapVariable: (SoapVariable name: 'auau' value: 'true' type: #Boolean). self should: [(ret getAttributeNamed: 'xsi:type') = 'xsd:boolean']. self should: [ret value = 'true'] ] testEncodeComplexNamedStruct [ "self debug: #testEncodeComplexNamedStruct" | element elems resultStruct enc var ret retResultElems retResultElem | element := SoapEncStruct fromAssociations: {#summary -> 'summary of squeak'} named: 'ResultElement'. elems := SoapEncArray fromArray: (Array with: element) named: 'resultElements' elementType: 'ResultElement'. resultStruct := SoapEncStruct fromAssociations: {#query -> 'squeak'. #resultElements -> elems}. self should: [resultStruct keys asArray = #('query' 'resultElements')]. enc := SoapEncoder new. var := SoapVariable name: 'SearchResult' value: resultStruct. ret := enc encodeSoapVariable: var. self should: [ret name = 'SearchResult']. retResultElems := ret findChildNamed: 'resultElements'. self should: [retResultElems notNil]. self should: [(ret findChildNamed: 'query') value = 'squeak']. self should: [retResultElems isArrayType]. self should: [retResultElems children size = 1]. self should: [retResultElems children size = 1]. retResultElem := retResultElems findChildNamed: 'item'. self should: [retResultElem notNil]. self should: [retResultElem notNil]. self should: [retResultElem xsiType = nil]. self should: [(retResultElem findChildNamed: 'summary') value = 'summary of squeak'] ] testEncodeComplexNamedStructShared [ "self debug: #testEncodeComplexNamedStructShared" | element elems resultStruct enc var ret retResultElems retResultElem retResultElems2 | element := SoapEncStruct fromAssociations: {#summary -> 'summary of squeak'} named: 'ResultElement'. elems := SoapEncArray fromArray: (Array with: element) named: 'resultElements' elementType: 'ResultElement'. resultStruct := SoapEncStruct fromAssociations: {#query -> 'squeak'. #resultElements -> elems. #resultElements2 -> elems} named: 'SearchResult'. self should: [resultStruct keys asArray = #('query' 'resultElements' 'resultElements2')]. enc := SoapEncoder new useSharedValues: true. var := SoapVariable name: 'SearchResult' value: resultStruct. ret := enc encodeSoapVariable: var. self should: [ret name = 'SearchResult']. retResultElems := ret findChildNamed: 'resultElements'. self should: [retResultElems notNil]. self should: [(ret findChildNamed: 'query') value = 'squeak']. self should: [retResultElems isArrayType]. self should: [retResultElems children size = 1]. self should: [retResultElems children size = 1]. retResultElem := retResultElems findChildNamed: 'item'. self should: [retResultElem notNil]. self should: [retResultElem notNil]. self should: [retResultElem xsiType = nil]. self should: [(retResultElem findChildNamed: 'summary') value = 'summary of squeak']. retResultElems2 := ret findChildNamed: 'resultElements2'. self should: [retResultElems id = (retResultElems2 href copyFrom: 2) asNumber] ] testEncodeFloatArray [ | enc ret | enc := SoapEncoder new. ret := enc encodeSoapVariable: (SoapVariable name: 'floatArr' value: #(1.0 2.3000000000000003 3.4000000000000004)). self should: [(ret getAttributeNamed: SoapConstants soapEncPrefixColon , 'arrayType') = 'xsd:float[3]']. self should: [(ret children at: 1) value = '1.0']. self should: [(ret children at: 3) value = '3.4000000000000004']. ret := enc encodeSoapVariable: (SoapVariable name: 'integarArr' value: #(4.5 5.600000000000001) type: #Array). self should: [(ret getAttributeNamed: SoapConstants soapEncPrefixColon , 'arrayType') = 'xsd:float[2]']. self should: [(ret children at: 1) value = '4.5']. self should: [(ret children at: 2) value = '5.600000000000001']. ret := enc encodeSoapVariable: (SoapVariable name: 'integarArr' value: #()). self should: [(ret getAttributeNamed: SoapConstants soapEncPrefixColon , 'arrayType') = 'xsd:anyType[0]']. self should: [ret children isEmpty] ] testEncodeInteger [ | enc ret | enc := SoapEncoder new. ret := enc encodeSoapVariable: (SoapVariable name: 'auau' value: 1). self should: [(ret getAttributeNamed: 'xsi:type') = 'xsd:integer']. self should: [ret value = '1']. ret := enc encodeSoapVariable: (SoapVariable name: 'auau' value: 10000000000 type: #Integer). self should: [(ret getAttributeNamed: 'xsi:type') = 'xsd:integer']. self should: [ret value = '10000000000'] ] testEncodeIntegerArray [ | enc ret | enc := SoapEncoder new. ret := enc encodeSoapVariable: (SoapVariable name: 'integarArr' value: #(1 2 3)). self should: [(ret getAttributeNamed: SoapConstants soapEncPrefixColon , 'arrayType') = 'xsd:integer[3]']. self should: [(ret children at: 1) value = '1']. self should: [(ret children at: 3) value = '3']. ret := enc encodeSoapVariable: (SoapVariable name: 'integarArr' value: #(4 5) type: #Array). self should: [(ret getAttributeNamed: SoapConstants soapEncPrefixColon , 'arrayType') = 'xsd:integer[2]']. self should: [(ret children at: 1) value = '4']. self should: [(ret children at: 2) value = '5']. ret := enc encodeSoapVariable: (SoapVariable name: 'integarArr' value: #()). self should: [(ret getAttributeNamed: SoapConstants soapEncPrefixColon , 'arrayType') = 'xsd:anyType[0]']. self should: [ret children isEmpty] ] testEncodeNil [ | originalUseNull enc ret | [originalUseNull := SoapEncoder useXsiNullAttribute. enc := SoapEncoder new. SoapEncoder useXsiNullAttribute: false. ret := enc encodeSoapVariable: (SoapVariable name: 'auau' value: nil). self should: [ret = nil]. SoapEncoder useXsiNullAttribute: true. ret := enc encodeSoapVariable: (SoapVariable name: 'auau' value: nil). self should: [ret name = 'auau']. self should: [(ret getAttributeNamed: SoapConstants xsiNil) = 1]] ensure: [SoapEncoder useXsiNullAttribute: originalUseNull] ] testEncodeReferredValue [ "self debug: #testEncodeReferredValue" | enc var1 var2 var3 ret1 ret2 ret3 | enc := SoapEncoder new. var1 := SoapVariable name: 'master' value: #MASTER. var2 := SoapVariable name: 'valueRef' href: var1. var2 value: 1. var3 := SoapVariable name: 'valueRefRef' href: var2. var3 value: 2. ret1 := enc encodeSoapVariable: var1. self should: [ret1 name = 'master']. self should: [(ret1 getAttributeNamed: 'xsi:type') = 'xsd:string']. self should: [ret1 value = 'MASTER']. self should: [ret1 hasAttributeNamed: 'id']. ret2 := enc encodeSoapVariable: var2. self should: [ret2 name = 'valueRef']. self shouldnt: [ret2 hasAttributeNamed: 'xsi:type']. self should: [ret2 value isNil]. self should: [ret2 hasAttributeNamed: 'href']. self should: [(ret2 getAttributeNamed: 'href') = ('#' , (ret1 getAttributeNamed: 'id'))]. ret3 := enc encodeSoapVariable: var3. self should: [ret3 name = 'valueRefRef']. self shouldnt: [ret3 hasAttributeNamed: 'xsi:type']. self should: [ret3 value isNil]. self should: [ret3 hasAttributeNamed: 'href']. self should: [(ret3 getAttributeNamed: 'href') = ('#' , (ret2 getAttributeNamed: 'id'))] ] testEncodeSimpleNamedStruct [ "self debug: #testEncodeSimpleNamedStruct" | enc ret dic struct | enc := SoapEncoder new. dic := {#varString -> 'hello'. #varInt -> 42. #varFloat -> 0.6000000000000001}. struct := SoapEncStruct fromAssociations: dic. ret := enc encodeSoapVariable: (SoapVariable name: 'inputStruct' value: struct xsdType: 'SearchResult'). self should: [ret name = 'inputStruct']. self should: [ret xsiType = 'SearchResult']. self should: [ret children size = 3]. self should: [(ret findChildNamed: 'varString') xsiType = SoapConstants xsdStringType]. self should: [(ret findChildNamed: 'varInt') xsiType = SoapConstants xsdIntegerType]. self should: [(ret findChildNamed: 'varFloat') xsiType = SoapConstants xsdFloatType]. self should: [(ret findChildNamed: 'varString') value = 'hello']. self should: [(ret findChildNamed: 'varInt') value = '42']. self should: [(ret findChildNamed: 'varFloat') value = '0.6000000000000001'] ] testEncodeSimpleStruct [ | enc ret dic | enc := SoapEncoder new. dic := Dictionary new. dic at: #varString put: 'hello'. dic at: #varInt put: 42. dic at: #varFloat put: 0.6000000000000001. ret := enc encodeSoapVariable: (SoapVariable name: 'inputStruct' value: dic). self should: [ret name = 'inputStruct']. self should: [ret children size = 3]. self should: [(ret findChildNamed: 'varString') xsiType = SoapConstants xsdStringType]. self should: [(ret findChildNamed: 'varInt') xsiType = SoapConstants xsdIntegerType]. self should: [(ret findChildNamed: 'varFloat') xsiType = SoapConstants xsdFloatType]. self should: [(ret findChildNamed: 'varString') value = 'hello']. self should: [(ret findChildNamed: 'varInt') value = '42']. self should: [(ret findChildNamed: 'varFloat') value = '0.6000000000000001'] ] testEncodeSimpleStructWithNamespace [ "self debug: #testEncodeSimpleStructWithNamespace" | enc ret dic struct | enc := SoapEncoder new. dic := {#varString -> 'hello'. #varInt -> 42. #varFloat -> 0.6000000000000001}. struct := SoapEncStruct fromAssociations: dic xsdType: 'ns2:SOAPStruct' namespace: 'http://www.aa.com/aaa'. ret := enc encodeSoapVariable: (SoapVariable name: 'inputStruct' value: struct). self should: [ret name = 'inputStruct']. self should: [(ret declaredNamespaceURIFor: 'ns2') = 'http://www.aa.com/aaa']. self should: [ret children size = 3]. self should: [(ret findChildNamed: 'varString') xsiType = SoapConstants xsdStringType]. self should: [(ret findChildNamed: 'varInt') xsiType = SoapConstants xsdIntegerType]. self should: [(ret findChildNamed: 'varFloat') xsiType = SoapConstants xsdFloatType]. self should: [(ret findChildNamed: 'varString') value = 'hello']. self should: [(ret findChildNamed: 'varInt') value = '42']. self should: [(ret findChildNamed: 'varFloat') value = '0.6000000000000001'] ] testEncodeString [ | enc ret | enc := SoapEncoder new. ret := enc encodeSoapVariable: (SoapVariable name: 'auau' value: 'smalltalk'). self should: [(ret getAttributeNamed: 'xsi:type') = 'xsd:string']. self should: [ret value = 'smalltalk']. ret := enc encodeSoapVariable: (SoapVariable name: 'auau' value: 'ruby' type: #String). self should: [(ret getAttributeNamed: 'xsi:type') = 'xsd:string']. self should: [ret value = 'ruby'] ] testEncodeStringArray [ | enc ret | enc := SoapEncoder new. ret := enc encodeSoapVariable: (SoapVariable name: 'stringArr' value: #('a' 'b' 'c')). self should: [(ret getAttributeNamed: SoapConstants soapEncPrefixColon , 'arrayType') = 'xsd:string[3]']. self should: [(ret children at: 1) value = 'a']. self should: [(ret children at: 3) value = 'c']. ret := enc encodeSoapVariable: (SoapVariable name: 'stringArr' value: #('' 'eee') type: #Array). self should: [(ret getAttributeNamed: SoapConstants soapEncPrefixColon , 'arrayType') = 'xsd:string[2]']. self should: [(ret children at: 1) value = '']. self should: [(ret children at: 2) value = 'eee']. ret := enc encodeSoapVariable: (SoapVariable name: 'stringArr' value: #()). self should: [(ret getAttributeNamed: SoapConstants soapEncPrefixColon , 'arrayType') = 'xsd:anyType[0]']. self should: [ret children isEmpty] ] ] TestCase subclass: SoapEnvelopeBuilderTestCase [ echoBoolean [ "From ROUND 2 SOAP Interoperability Tests Specification" "http://www.whitemesa.com/interop/proposal2.html#echoInteger" ^' 1 ' ] echoInteger [ "From ROUND 2 SOAP Interoperability Tests Specification" "http://www.whitemesa.com/interop/proposal2.html#echoInteger" ^' 42 ' ] testBuildClientSoapFaultEnvelope [ | builder env body fault | builder := SoapEnvelopeBuilder new. env := builder buildClientSoapFaultEnvelope: (ZeroDivide dividend: 'test zero divide'). body := env body. self should: [body name = 'env:Body']. self should: [body hasFault]. fault := body fault. self should: [fault name = 'env:Fault']. self should: [fault faultcode = 'env:Client'] ] testBuildEnvelope [ | builder env body methodElem argElem | builder := SoapEnvelopeBuilder new. env := builder buildSoapEnvelopeFromXmlString: self echoInteger. self should: [env name = 'SOAP-ENV:Envelope']. self should: [(env getAttributeNamed: 'SOAP-ENV:encodingStyle') = 'http://schemas.xmlsoap.org/soap/encoding/']. " self should: [(env getAttributeNamed: 'xmlns:SOAP-ENC') = 'http://schemas.xmlsoap.org/soap/encoding/']. self should: [(env getAttributeNamed: 'xmlns:SOAP-ENV') = 'http://schemas.xmlsoap.org/soap/envelope/']. self should: [(env getAttributeNamed: 'xmlns:xsd') = 'http://www.w3.org/2001/XMLSchema']. self should: [(env getAttributeNamed: 'xmlns:xsi') = 'http://www.w3.org/2001/XMLSchema-instance']. " body := env body. self should: [body name = 'SOAP-ENV:Body']. methodElem := body findBodyEntryNamed: 'm:echoInteger'. self should: [methodElem notNil]. self should: [methodElem name = 'm:echoInteger']. " self should: [(methodElem getAttributeNamed: 'xmlns:m') = 'http://soapinterop.org/']. " argElem := methodElem children first. self should: [argElem name = 'inputInteger']. self should: [argElem value = '42'] ] testInheritedEnvelopeEncoding [ | builder env body methodElem argElem | builder := SoapEnvelopeBuilder new. env := builder buildSoapEnvelopeFromXmlString: self echoBoolean. self should: [env name = 'SOAP-ENV:Envelope']. self should: [env encodingStyleURIs = #('http://schemas.xmlsoap.org/soap/encoding/')]. body := env body. self should: [body name = 'SOAP-ENV:Body']. methodElem := body findBodyEntryNamed: 'm:echoBoolean'. self should: [methodElem notNil]. self should: [methodElem name = 'm:echoBoolean']. " self should: [(methodElem getAttributeNamed: 'xmlns:m') = 'http://soapinterop.org/']. " argElem := methodElem children first. self should: [argElem encodingStyleURIs = #('http://schemas.xmlsoap.org/soap/encoding/')]. self should: [argElem name = 'inputBoolean']. self should: [argElem value = '1'] ] ]