smalltalk
/
osmo-st-all
Archived
1
0
Fork 0

soap: Add more test cases.

This commit is contained in:
Holger Hans Peter Freyther 2011-02-20 22:16:36 +01:00
parent bd0ff831aa
commit 4672e44233
1 changed files with 468 additions and 0 deletions

View File

@ -1300,3 +1300,471 @@ TestCase subclass: SoapEncStructTestCase [
]
TestCase subclass: SoapEncoderTestCase [
<comment: nil>
<category: 'SOAP-TestCases'>
testEncodeBase64Binary [
"self debug: #testEncodeBase64Binary"
<category: 'testing'>
| 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 [
<category: 'testing'>
| 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"
<category: 'testing'>
| 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"
<category: 'testing'>
| 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 [
<category: 'testing'>
| 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 [
<category: 'testing'>
| 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 [
<category: 'testing'>
| 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 [
<category: 'testing'>
| 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"
<category: 'testing'>
| 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"
<category: 'testing'>
| 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 [
<category: 'testing'>
| 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"
<category: 'testing'>
| 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 [
<category: 'testing'>
| 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 [
<category: 'testing'>
| 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 [
<comment: nil>
<category: 'SOAP-TestCases'>
echoBoolean [
"From ROUND 2 SOAP Interoperability Tests Specification"
"http://www.whitemesa.com/interop/proposal2.html#echoInteger"
<category: 'fixtures'>
^'<?xml version="1.0" encoding="UTF-8"?>
<SOAP-ENV:Envelope xmlns:SOAP-ENV="http://schemas.xmlsoap.org/soap/envelope/" xmlns:SOAP-ENC="http://schemas.xmlsoap.org/soap/encoding/" xmlns:xsd="http://www.w3.org/2001/XMLSchema" xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" SOAP-ENV:encodingStyle="http://schemas.xmlsoap.org/soap/encoding/">
<SOAP-ENV:Body>
<m:echoBoolean xmlns:m="http://soapinterop.org/">
<inputBoolean>1</inputBoolean>
</m:echoBoolean>
</SOAP-ENV:Body>
</SOAP-ENV:Envelope>'
]
echoInteger [
"From ROUND 2 SOAP Interoperability Tests Specification"
"http://www.whitemesa.com/interop/proposal2.html#echoInteger"
<category: 'fixtures'>
^'<?xml version="1.0" encoding="UTF-8"?>
<SOAP-ENV:Envelope SOAP-ENV:encodingStyle="http://schemas.xmlsoap.org/soap/encoding/" xmlns:SOAP-ENC="http://schemas.xmlsoap.org/soap/encoding/" xmlns:SOAP-ENV="http://schemas.xmlsoap.org/soap/envelope/" xmlns:xsd="http://www.w3.org/2001/XMLSchema" xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance">
<SOAP-ENV:Body>
<m:echoInteger xmlns:m="http://soapinterop.org/">
<inputInteger>42</inputInteger>
</m:echoInteger>
</SOAP-ENV:Body>
</SOAP-ENV:Envelope>'
]
testBuildClientSoapFaultEnvelope [
<category: 'testing'>
| 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 [
<category: 'testing'>
| 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 [
<category: 'testing'>
| 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']
]
]