smalltalk
/
osmo-st-all
Archived
1
0
Fork 0
This repository has been archived on 2022-02-17. You can view files and clone it, but cannot push or open issues or pull requests.
osmo-st-all/soapopera/UnportedTestCases.st

1255 lines
34 KiB
Smalltalk
Raw Blame History

This file contains invisible Unicode characters

This file contains invisible Unicode characters that are indistinguishable to humans but may be processed differently by a computer. If you think that this is intentional, you can safely ignore this warning. Use the Escape button to reveal them.

TestCase subclass: SoSoapFaultDetailBuilderTestCase [
<comment: nil>
<category: 'SOAP-TestCases'>
doItInWorkspace [
"SoSoapFaultDetailBuilderTestCase new doItInWorkspace"
<category: 'for workspace'>
| soapFaultDetail res1 res2 res3 details res4 res5 res6 results |
soapFaultDetail := [1 / 0] on: Error
do:
[:ex |
| build de |
build := SoapFaultDetailBuilder new.
de := build buildSoapFaultDetailOn: SoapFault server from: ex.
de].
res1 := soapFaultDetail parent name = 'SOAP-ENV:Fault'.
res2 := soapFaultDetail parent faultstring = 'ZeroDivide'.
res3 := soapFaultDetail name = 'detail'.
details := soapFaultDetail subElements first.
res4 := details shortName = 'details'.
res5 := (details
declaredNamespaceURIFor: SoapFaultDetailBuilder defaultPrefix)
= SoapFaultDetailBuilder defaultNamespace.
res6 := (details findChildNamed: 'ErrorClass') value = 'ZeroDivide'.
results := OrderedCollection new.
results add: res1.
results add: res2.
results add: res3.
results add: res4.
results add: res5.
results add: res6.
results inspect
]
testBuildSoapFaultDetailWithZeroDivide [
"###COULD NOT RUN - BECAUSE OF SUNIT ERROR###"
"DO it in workspace instead"
"| soapFaultDetail details |
soapFaultDetail := [1 / 0]
on: ZeroDivide
do: [:ex |
| build de |
build := SoapFaultDetailBuilder new.
de := build buildSoapFaultDetailOn: SoapFault server from: ex.
de].
self should: [soapFaultDetail parent name = 'SOAP-ENV:Fault'].
self should: [soapFaultDetail parent faultstring = 'ZeroDivide'].
self should: [soapFaultDetail name = 'detail'].
details := soapFaultDetail subElements first.
self should: [details shortName = 'details'].
self should: [(details declaredNamespaceURIFor: SoapFaultDetailBuilder defaultPrefix)
= SoapFaultDetailBuilder defaultNamespace].
self should:[ (details findChildNamed: 'ErrorClass') value = 'ZeroDivide']."
<category: 'testing'>
]
]
TestCase subclass: SoapCallTestCase [
| originalTransports |
<comment: nil>
<category: 'SOAP-TestCases'>
SoapCallTestCase class >> waitAMoment [
<category: 'utility'>
(SmalltalkImage current platformName asLowercase beginsWith: 'win')
ifTrue: [^self].
(Delay forMilliseconds: 100) wait
]
setUp [
<category: 'running'>
originalTransports := SoapServerSetup runningTransportNames
]
simpleAddService [
<category: 'fixtures'>
| ord serv |
ord := OrderedCollection new.
serv := SoapService implementor: ord selector: #add:.
serv signature: (SoapServiceSignature name: 'add' paramNames: #(#newElem)).
^serv
]
tearDown [
<category: 'running'>
SoapServerSetup startOnly: originalTransports
]
testAnyArrayHttpCall [
<category: 'testing'>
| handlerName call resp |
SoapServerSetup startOnly: #(#http).
self waitAMoment.
handlerName := SoapServiceHandler useTestServiceHandler
ifTrue: [#test]
ifFalse: [#default].
(SoapServiceHandler named: handlerName) add: self simpleAddService.
call := (SoapCallEntry local: (SoapServerSetup defaultPortAt: #http))
newCall.
call transport: #http.
call methodName: 'add'.
call addParameter: (SoapVariable name: #newElem value: #(1.0 'two' 3)).
resp := call invoke.
self shouldnt: [resp isFault].
self should: [resp returnValue = #(1.0 'two' 3)].
(SoapServiceHandler named: handlerName) remove: self simpleAddService
]
testCannotConnectHttpCall [
<category: 'testing'>
| notUsedPort call resp |
notUsedPort := 9876.
call := (SoapCallEntry tcpHost: 'localhost' port: notUsedPort) newCall.
call transport: #http.
call methodName: 'helloWorld'.
resp := call invoke.
self should: [resp isFault].
self should: [resp returnValue = nil].
self should: [resp raiseException] raise: SoapCannotConnectToServer
]
testCannotConnectResolveCall [
<category: 'testing'>
| call resp |
call := (SoapCallEntry tcpHost: 'foobarbazboo' port: 8823) newCall.
call transport: #http.
call methodName: 'helloWorld'.
resp := call invoke.
self should: [resp isFault].
self should: [resp returnValue = nil].
self should: [resp raiseException] raise: SoapCannotResolveServer
]
testCannotResolveHttpCall [
<category: 'testing'>
| notUsedPort call resp |
notUsedPort := 9876.
call := (SoapCallEntry tcpHost: 'localhost' port: notUsedPort) newCall.
call transport: #http.
call methodName: 'helloWorld'.
resp := call invoke.
self should: [resp isFault].
self should: [resp returnValue = nil].
self should: [resp raiseException] raise: SoapCannotConnectToServer
]
testComplexSqEncoding [
<category: 'testing'>
| call pa1 pa2 env methodElem arg1 arg2 |
call := SoapCall new.
call transport: #localRpc.
call targetObjectURI: 'urn:auauObject'.
call encoding: #soapSqEncoding.
call methodName: 'auau'.
pa1 := SoapVariable name: #arg1 value: 1.
pa2 := (SoapVariable name: #arg2 value: #two) encoding: #soapSqEncoding.
call addParameter: pa1.
call addParameter: pa2.
env := call buildEnvelope.
self should: [env name = 'env:Envelope'].
self should: [env body name = 'env:Body'].
self should:
[(env getAttributeNamed: 'env:encodingStyle') = SoapConstants soapSqEncURI].
methodElem := env body bodyEntries first.
self should: [methodElem name = 'm:auau'].
arg1 := methodElem children at: 1.
self should: [arg1 name = 'arg1'].
self should: [(arg1 getAttributeNamed: 'xsi:type') = 'xsd:integer'].
self should: [arg1 encodingStyleURIs first = SoapConstants soapSqEncURI].
self should: [arg1 value = '1'].
arg2 := methodElem children at: 2.
self should: [arg2 name = 'arg2'].
self
should: [(arg2 getAttributeNamed: 'xsi:type') = 'Squeak-ENC:ReferenceStream']
]
testComplexSqHttpCall [
<category: 'testing'>
| handlerName call resp |
SoapServerSetup startOnly: #(#http).
self waitAMoment.
handlerName := SoapServiceHandler useTestServiceHandler
ifTrue: [#test]
ifFalse: [#default].
(SoapServiceHandler named: handlerName) add: self simpleAddService.
call := (SoapCallEntry local: (SoapServerSetup defaultPortAt: #http))
newCall.
call transport: #http.
call encoding: #soapSqEncoding.
call methodName: 'add'.
call addParameter: (SoapVariable name: #newElem).
resp := call invokeWithValue: #symbol.
self shouldnt: [resp isFault].
self should: [resp returnValue = #symbol].
resp := call invokeWithValue: Date today.
self shouldnt: [resp isFault].
self should: [resp returnValue = Date today].
resp := call invokeWithValue: (OrderedCollection
with: #(1 2 #('three' 3) #with: #Date #today)).
self shouldnt: [resp isFault].
self should:
[resp returnValue
= (OrderedCollection with: #(1 2 #('three' 3) #with: #Date #today))].
(SoapServiceHandler named: handlerName) remove: self simpleAddService
]
testDefaultEncodingCreation [
<category: 'testing'>
| call |
call := SoapCall new.
call targetObjectURI: 'urn:target:1'.
call encoding: #soapEncoding.
self should: [call encoder class = SoapEncoder]
]
testIntegerArrayHttpCall [
<category: 'testing'>
| handlerName call resp |
SoapServerSetup startOnly: #(#http).
self waitAMoment.
handlerName := SoapServiceHandler useTestServiceHandler
ifTrue: [#test]
ifFalse: [#default].
(SoapServiceHandler named: handlerName) add: self simpleAddService.
call := (SoapCallEntry local: (SoapServerSetup defaultPortAt: #http))
newCall.
call transport: #http.
call methodName: 'add'.
call addParameter: (SoapVariable name: #newElem value: #(1 2 3)).
resp := call invoke.
self shouldnt: [resp isFault].
self should: [resp returnValue = #(1 2 3)].
(SoapServiceHandler named: handlerName) remove: self simpleAddService
]
testSimpleColocationCall [
"self debug: #testSimpleColocationCall"
<category: 'testing'>
| call resp |
SoapServerSetup startOnly: #(#http).
self waitAMoment.
SoapServiceHandler default add: self simpleAddService.
call := SoapCallEntry local newCall.
self should: [call useColocation == false].
call methodName: 'add'.
call addParameter: (SoapVariable name: #newElem value: 1).
resp := call invoke.
self shouldnt: [resp isFault].
self should: [resp returnValue = 1].
self should: [call transport == #http].
self should: [call colocated].
call useColocation: true.
resp := call invoke.
self shouldnt: [resp isFault].
self should: [resp returnValue = 1].
self should: [call transport == #http].
self should: [call connector isKindOf: SoapLocalRpcConnector].
SoapServiceHandler default remove: self simpleAddService
]
testSimpleEnvelopeCreatein [
<category: 'testing'>
| call env methodElem arg1 arg2 |
call := SoapCall new.
call methodName: 'auau'.
call addParameter: (SoapVariable name: #arg1 value: 1).
call addParameter: (SoapVariable name: #arg2 value: 'two').
env := call buildEnvelope.
self should: [env name = 'env:Envelope'].
self should: [env body name = 'env:Body'].
methodElem := env body bodyEntries first.
self should: [methodElem name = 'm:auau'].
arg1 := methodElem children at: 1.
self should: [arg1 name = 'arg1'].
self should: [arg1 xsiType = 'xsd:integer'].
self should: [arg1 value = '1'].
arg2 := methodElem children at: 2.
self should: [arg2 name = 'arg2'].
self should: [arg2 xsiType = 'xsd:string'].
self should: [arg2 value = 'two']
]
testSimpleEnvelopeCreateinForDocumentLiteral [
"self debug: #testSimpleEnvelopeCreateinForDocumentLiteral"
<category: 'testing'>
| call env arg1 arg2 paramElems |
call := (SoapCallEntry tcpHost: 'www.somehost.com' port: 80) newCall.
call style: #document.
call useLiteral: true.
call addParameters:
{
{#xElement.
1.2000000000000002}.
{#yElement.
2.0}}.
env := call buildEnvelope.
self should: [env name = 'env:Envelope'].
self should: [env body name = 'env:Body'].
paramElems := env body bodyEntries.
arg1 := paramElems at: 1.
self should: [arg1 name = 'xElement'].
self should: [arg1 xsiType = nil].
self should: [arg1 value = '1.2'].
arg2 := paramElems at: 2.
self should: [arg2 name = 'yElement'].
self should: [arg2 xsiType = nil].
self should: [arg2 value = '2.0']
]
testSimpleHttpCall [
<category: 'testing'>
| handlerName call resp |
SoapServerSetup startOnly: #(#http).
self waitAMoment.
handlerName := SoapServiceHandler useTestServiceHandler
ifTrue: [#test]
ifFalse: [#default].
(SoapServiceHandler named: handlerName) add: self simpleAddService.
call := (SoapCallEntry local: (SoapServerSetup defaultPortAt: #http))
newCall.
call transport: #http.
call methodName: 'add'.
call addParameter: (SoapVariable name: #newElem value: 1).
resp := call invoke.
self shouldnt: [resp isFault].
self should: [resp returnValue = 1].
(SoapServiceHandler named: handlerName) remove: self simpleAddService
]
testSimpleHttpCallWithError [
<category: 'testing'>
| handlerName call resp |
SoapServerSetup startOnly: #(#http).
self waitAMoment.
handlerName := SoapServiceHandler useTestServiceHandler
ifTrue: [#test]
ifFalse: [#default].
(SoapServiceHandler named: handlerName) add: self simpleAddService.
call := (SoapCallEntry local: (SoapServerSetup defaultPortAt: #http))
newCall.
call methodName: 'add'.
call addParameter: (SoapVariable name: #badArg1 value: 1).
resp := call invoke.
self should: [resp isFault].
self should: [resp returnValue = nil].
self should: [resp raiseException] raise: SoapInvalidParamName.
(SoapServiceHandler named: handlerName) remove: self simpleAddService
]
testSimpleLocalCall [
"self debug: #testSimpleLocalCall"
<category: 'testing'>
| call resp |
SoapServiceHandler default add: self simpleAddService.
call := SoapCallEntry local newCall.
call transport: #localRpc.
call methodName: 'add'.
call addParameter: (SoapVariable name: #newElem value: 1).
resp := call invoke.
self shouldnt: [resp isFault].
self should: [resp returnValue = 1].
SoapServiceHandler default remove: self simpleAddService
]
testSimpleLocalCallChangeStyle [
"SoapCallTestCase debug: #testSimpleLocalCallChangeStyle"
"Currently, SoapCore server does not support document type binding, So, this tests client side only"
<category: 'testing'>
| call resp |
call := SoapCallEntry local newCall.
call transport: #localRpc.
call methodName: 'sendDocument'.
call addParameter: (SoapVariable name: #sendDocument value: 'some doc').
call style: #document.
resp := call invoke.
self should: [resp isFault].
self should: [resp style = #document]
]
testSimpleLocalCallWithError [
<category: 'testing'>
| call resp |
SoapServiceHandler default add: self simpleAddService.
call := SoapCallEntry local newCall.
call transport: #localRpc.
call methodName: 'add'.
call addParameter: (SoapVariable name: #badArg1 value: 1).
resp := call invoke.
self should: [resp isFault].
self should: [resp returnValue = nil].
self should: [resp raiseException] raise: SoapInvalidParamName.
SoapServiceHandler default remove: self simpleAddService
]
testSimpleSqCall [
<category: 'testing'>
| call resp |
SoapServiceHandler default add: self simpleAddService.
call := SoapCallEntry local newCall.
call transport: #localRpc.
call encoding: #soapSqEncoding.
call methodName: 'add'.
call addParameter: (SoapVariable name: #newElem value: 1).
resp := call invoke.
self shouldnt: [resp isFault].
self should: [resp returnValue = 1].
SoapServiceHandler default remove: self simpleAddService
]
testSimpleSqHttpCall [
<category: 'testing'>
| handlerName call resp |
SoapServerSetup startOnly: #(#http).
self waitAMoment.
handlerName := SoapServiceHandler useTestServiceHandler
ifTrue: [#test]
ifFalse: [#default].
(SoapServiceHandler named: handlerName) add: self simpleAddService.
call := (SoapCallEntry local: (SoapServerSetup defaultPortAt: #http))
newCall.
call transport: #http.
call encoding: #soapSqEncoding.
call methodName: 'add'.
call addParameter: (SoapVariable name: #newElem value: 1).
resp := call invoke.
self shouldnt: [resp isFault].
self should: [resp returnValue = 1].
(SoapServiceHandler named: handlerName) remove: self simpleAddService
]
testSqEncodingCreation [
<category: 'testing'>
| call |
call := SoapCall new.
call targetObjectURI: 'urn:target:1'.
call encoding: #soapSqEncoding.
self should: [call encoder class = SoapSqEncoder]
]
waitAMoment [
<category: 'private'>
self class waitAMoment
]
]
TestCase subclass: SoapConnectorTestCase [
<comment: nil>
<category: 'SOAP-TestCases'>
testCreateConnector [
<category: 'testing'>
| con |
con := SoapConnectorFactory createFrom: #http.
self should: [con class = SoapHttpConnector].
self should: [SoapConnectorFactory createFrom: #auau]
raise: SoapNoSuchConnector
]
]
TestCase subclass: SoapHttpClientTestCase [
| originalTransports |
<comment: nil>
<category: 'SOAP-TestCases'>
errorEnvelope [
<category: 'fixtures'>
^'
<env:Envelope
xmlns:env="http://schemas.xmlsoap.org/soap/envelope/"
env:encodingStyle="http://schemas.xmlsoap.org/soap/encoding/">
<env:Body>
<m:DoSomeOtherThing xmlns:m="urn:stSoap:Person1234">
<symbol>DIS</symbol>
</m:DoSomeOtherThing>
</env:Body>
</env:Envelope>
'
copy
]
setUp [
<category: 'running'>
originalTransports := SoapServerSetup runningTransportNames.
SoapServerSetup startOnly: #(#http)
]
simpleEnvelope [
<category: 'fixtures'>
^'
<env:Envelope
xmlns:env="http://schemas.xmlsoap.org/soap/envelope/"
env:encodingStyle="http://schemas.xmlsoap.org/soap/encoding/">
<env:Body>
<m:add xmlns:m="http://www.mars.dti.ne.jp/~umejava/smalltalk/soapOpera/">
<newElem>newElement</newElem>
</m:add>
</env:Body>
</env:Envelope>
'
copy
]
simpleService [
<category: 'fixtures'>
| ord serv |
ord := OrderedCollection new.
serv := SoapService implementor: ord selector: #add:.
serv signature: (SoapServiceSignature name: 'add' paramNames: #(#newElem)).
^serv
]
tearDown [
<category: 'running'>
SoapServerSetup startOnly: originalTransports
]
testErrorEnvelopeSend [
<category: 'testing'>
| curPort retXML envelope body prefix fault |
SoapServerSetup startOnly: #(#http).
SoapCallTestCase waitAMoment.
SoapServiceHandler default add: self simpleService.
curPort := SoapSetting defaultPortAt: #http.
retXML := (SoapHttpClient
url: 'http://localhost:' , curPort printString , '/')
send: self errorEnvelope.
envelope := SoapEnvelopeBuilder new buildSoapEnvelopeFromXmlString: retXML.
self should: [envelope isKindOf: SoapEnvelope].
body := envelope body.
self should: [body hasFault].
fault := body fault.
prefix := SoapConstants soapEnvPrefixColon.
self should: [fault name = (prefix , 'Fault')].
self should: [fault faultcode = (prefix , 'Client')].
self should: [fault faultstring = 'SoapNoSuchService: DoSomeOtherThing'].
SoapServiceHandler default remove: self simpleService
]
testSimpleEnvelopeSend [
"SoapHttpClientTestCase debug: #testSimpleEnvelopeSend"
<category: 'testing'>
| curPort retXML envelope body method |
SoapServerSetup startOnly: #(#http).
SoapCallTestCase waitAMoment.
SoapServiceHandler default add: self simpleService.
curPort := SoapSetting defaultPortAt: #http.
retXML := (SoapHttpClient
url: 'http://localhost:' , curPort printString , '/')
send: self simpleEnvelope.
envelope := SoapEnvelopeBuilder new buildSoapEnvelopeFromXmlString: retXML.
self should: [envelope isKindOf: SoapEnvelope].
body := envelope body.
self shouldnt: [body hasFault].
method := body bodyEntries first.
self should: [method name = 'm:addResponse'].
self should: [(method findChildNamed: 'result') value = 'newElement'].
SoapServiceHandler default remove: self simpleService
]
]
TestCase subclass: SoapServiceHandlerTestCase [
<comment: nil>
<category: 'SOAP-TestCases'>
defaultTargetObjectURI [
<category: 'fixtures'>
^'http://www.fooServer.com/OrderedCollection'
]
errorEnvelope [
<category: 'fixtures'>
| xmlStr env |
xmlStr := self errorEnvelopeXml.
env := SoapEnvelopeBuilder new buildSoapEnvelopeFromXmlString: xmlStr.
^env
]
errorEnvelopeXml [
<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:adddd xmlns:m="http://soapinterop.org/">
<newElem>1</newElem>
</m:adddd>
</SOAP-ENV:Body>
</SOAP-ENV:Envelope>'
]
referenceUsingEnvelope [
<category: 'fixtures'>
| xmlStr env |
xmlStr := self referenceUsingEnvelopeXml.
env := SoapEnvelopeBuilder new buildSoapEnvelopeFromXmlString: xmlStr.
^env
]
referenceUsingEnvelopeXml [
<category: 'fixtures'>
^'<?xml version="1.0" encoding="utf-8"?>
<soapenv:Envelope
xmlns:soapenv="http://schemas.xmlsoap.org/soap/envelope/"
xmlns:xsd="http://www.w3.org/2001/XMLSchema"
xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance">
<soapenv:Body>
<ns1:getAvailableLockers
soapenv:encodingStyle="http://schemas.xmlsoap.org/soap/encoding/"
xmlns:ns1="urn:SoftLocker">
<clientTag href="#id0"/>
<postCode xsi:type="xsd:string">RH1 6NT</postCode>
</ns1:getAvailableLockers>
<multiRef id="id0" soapenc:root="0"
soapenv:encodingStyle="http://schemas.xmlsoap.org/soap/encoding/"
xsi:type="xsd:integer"
xmlns:soapenc="http://schemas.xmlsoap.org/soap/encoding/">4242</multiRef>
</soapenv:Body>
</soapenv:Envelope>
'
]
referenceUsingService [
<category: 'fixtures'>
| impl serv |
impl := SoapMockServiceImplForReferenceUsing new.
serv := SoapService implementor: impl
selector: #getAvailableLockers:postCode:.
serv setSignatureNamed: 'getAvailableLockers'
paramNames: #(#clientTag #postCode).
serv targetObjectURI: self defaultTargetObjectURI.
^serv
]
simpleContext [
<category: 'fixtures'>
^SoapContext new targetObjectURI: self defaultTargetObjectURI
]
simpleEnvelope [
<category: 'fixtures'>
| xmlStr env |
xmlStr := self simpleEnvelopeXml.
env := SoapEnvelopeBuilder new buildSoapEnvelopeFromXmlString: xmlStr.
^env
]
simpleEnvelopeWithXsdType [
<category: 'fixtures'>
| xmlStr env |
xmlStr := self simpleEnvelopeXmlWithXsdType.
env := SoapEnvelopeBuilder new buildSoapEnvelopeFromXmlString: xmlStr.
^env
]
simpleEnvelopeXml [
<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:add xmlns:m="http://soapinterop.org/">
<newElem>1</newElem>
</m:add>
</SOAP-ENV:Body>
</SOAP-ENV:Envelope>'
]
simpleEnvelopeXmlWithXsdType [
<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:add xmlns:m="http://soapinterop.org/">
<newElem xsi:type="xsd:float">1.02</newElem>
</m:add>
</SOAP-ENV:Body>
</SOAP-ENV:Envelope>'
]
simpleService [
<category: 'fixtures'>
| ord serv |
ord := OrderedCollection new.
serv := SoapService implementor: ord selector: #add:.
serv signature: (SoapServiceSignature name: 'add' paramNames: #(#newElem)).
serv targetObjectURI: self defaultTargetObjectURI.
^serv
]
testDispatchError [
<category: 'testing'>
| handler env fault details |
handler := SoapServiceHandler new.
handler add: self simpleService.
env := self errorEnvelope.
"self shouldnt:[env := handler dispatch: env with: self simpleContext.] raise: Error."
env := handler dispatch: env with: self simpleContext.
self assert: env body hasFault.
fault := env body fault.
self should: [fault name = 'env:Fault'].
self should: [fault faultcode = 'env:Client'].
self
should: [fault faultstring = 'SoapNoSuchService: /OrderedCollection:adddd'].
details := fault detail subElements first.
self should: [details shortName = 'details'].
self should:
[(details declaredNamespaceURIFor: SoapFaultDetailBuilder defaultPrefix)
= SoapFaultDetailBuilder defaultNamespace].
self
should: [(details findChildNamed: 'ErrorClass') value = 'SoapNoSuchService']
]
testDispatchSimple [
<category: 'testing'>
| handler env ret |
handler := SoapServiceHandler new.
handler add: self simpleService.
env := handler dispatch: self simpleEnvelope with: self simpleContext.
self shouldnt: [env body hasFault].
ret := env body bodyEntries first.
self should: [ret name = 'm:addResponse'].
self should:
[ret encodingStyleURIs = #('http://schemas.xmlsoap.org/soap/encoding/')].
self should: [ret firstChild xsiType = 'xsd:string'].
self should: [ret firstChild value = '1']
]
testDispatchSimpleWithXsdType [
<category: 'testing'>
| handler env ret |
handler := SoapServiceHandler new.
handler add: self simpleService.
env := handler dispatch: self simpleEnvelopeWithXsdType
with: self simpleContext.
self shouldnt: [env body hasFault].
ret := env body bodyEntries first.
self should: [ret name = 'm:addResponse'].
self should:
[ret encodingStyleURIs = #('http://schemas.xmlsoap.org/soap/encoding/')].
self should: [ret firstChild xsiType = 'xsd:float'].
self should: [ret firstChild value = '1.02']
]
testDispatchSoapNoSuchServiceError [
<category: 'testing'>
| handler env fault |
handler := SoapServiceHandler new.
handler add: self simpleService.
env := self errorEnvelope.
self shouldnt: [env := handler dispatch: env with: self simpleContext]
raise: Error.
self assert: env body hasFault.
fault := env body fault
]
testInvokeReferenceUsing [
"SoapServiceHandlerTestCase debug: #testInvokeReferenceUsing"
<category: 'testing'>
| handler ret |
handler := SoapServiceHandler new.
handler add: self referenceUsingService.
ret := handler invoke: self referenceUsingEnvelope with: self simpleContext.
self should: [ret size = 2].
self should: [ret first = 4242].
self should: [ret second = 'RH1 6NT']
]
testInvokeSimple [
<category: 'testing'>
| handler ret |
handler := SoapServiceHandler new.
handler add: self simpleService.
ret := handler invoke: self simpleEnvelope with: self simpleContext.
self should: [ret = '1']
]
testInvokeSimpleWithXsdType [
<category: 'testing'>
| handler ret |
handler := SoapServiceHandler new.
handler add: self simpleService.
ret := handler invoke: self simpleEnvelopeWithXsdType
with: self simpleContext.
self should: [ret = 1.02]
]
testRegisterRemoveAll [
"self debug: #testRegisterAll"
<category: 'testing'>
| mockImpl services |
mockImpl := SoapMockServiceImpl new.
SoapServiceHandler registerAllIn: mockImpl.
services := SoapServiceHandler default
selectServices: [:each | each implementor = mockImpl].
self should: [services size = 3].
self
should: [services anySatisfy: [:each | each selector = #doSomething:]].
self
should: [services anySatisfy: [:each | each selector = #doSomething:with:]].
self should:
[services anySatisfy: [:each | each selector = #doSomething:with:with:]].
SoapServiceHandler removeAllIn: mockImpl.
services := SoapServiceHandler default
selectServices: [:each | each implementor = mockImpl].
self should: [services size = 0]
]
]
TestCase subclass: SoapServiceTestCase [
<comment: nil>
<category: 'SOAP-TestCases'>
testInvole [
<category: 'testing'>
| ord serv |
ord := OrderedCollection new.
serv := SoapService implementor: ord selector: #add:.
serv
signature: (SoapServiceSignature name: 'add' paramNames: #(#newObject)).
serv
invoke: ((SoapServiceSignature name: 'add' paramNames: #(#newObject))
valueAt: #newObject
put: #bar).
self should: [ord size = 1].
self should: [ord first = #bar]
]
testInvoleFail [
<category: 'testing'>
| ord serv |
ord := OrderedCollection new.
serv := SoapService implementor: ord selector: #add:.
serv
signature: (SoapServiceSignature name: 'add' paramNames: #(#newObject)).
self should:
[serv
invoke: ((SoapServiceSignature name: 'auau' paramNames: #(#newObject))
valueAt: #newObject
put: #bar)]
raise: SoapNoSuchService
]
testInvoleInvalidParamName [
<category: 'testing'>
| ord serv |
ord := OrderedCollection new.
serv := SoapService implementor: ord selector: #add:.
serv
signature: (SoapServiceSignature name: 'add' paramNames: #(#newObject)).
self should:
[serv
invoke: ((SoapServiceSignature name: 'add' paramNames: #(#newObject))
valueAt: #auauObject
put: #bar)]
raise: SoapInvalidParamName
]
testInvoleTwoArgs [
<category: 'testing'>
| dict serv regSig perSig |
dict := Dictionary new.
serv := SoapService implementor: dict selector: #at:put:.
regSig := SoapServiceSignature name: 'at put' paramNames: #(#index #value).
serv signature: regSig.
perSig := SoapServiceSignature name: 'at put' paramNames: #(#index #value).
perSig valueAt: #index put: 1.
perSig valueAt: #value put: #bar.
serv invoke: perSig.
self should: [dict includesKey: 1].
self should: [(dict at: 1) = #bar]
]
]
TestCase subclass: SoapSqDecoderTestCase [
<comment: nil>
<category: 'SOAP-TestCases'>
testDecodeBoolean [
<category: 'testing'>
| dec ret |
dec := SoapSqDecoder new.
ret := dec decodeXmlElement: ((SoapVariable
name: 'arg1'
value: 'true'
type: #Boolean)
encoding: #soapSqEncoding;
asXmlElement).
self should: [ret = true]
]
testDecodeInteger [
<category: 'testing'>
| dec ret |
dec := SoapSqDecoder new.
ret := dec decodeXmlElement: ((SoapVariable
name: 'arg1'
value: '1234567'
type: #Integer)
encoding: #soapSqEncoding;
asXmlElement).
self should: [ret = 1234567]
]
testDecodeObject [
<category: 'testing'>
| dec ret dict |
dec := SoapSqDecoder new.
dict := Dictionary new.
dict at: #Smalltalk put: #Cool.
dict at: #Java put: #Plain.
ret := dec decodeXmlElement: ((SoapVariable name: 'arg1' value: dict)
encoding: #soapSqEncoding;
asXmlElement).
self should: [ret = dict]
]
testDecodeString [
<category: 'testing'>
| dec ret |
dec := SoapSqDecoder new.
ret := dec decodeXmlElement: ((SoapVariable
name: 'arg1'
value: 'Smalltalk'
type: #String)
encoding: #soapSqEncoding;
asXmlElement).
self should: [ret = 'Smalltalk']
]
]
TestCase subclass: SoapSqEncoderTestCase [
<comment: nil>
<category: 'SOAP-TestCases'>
testEncodingInteger [
<category: 'testing'>
| enc ret |
enc := SoapSqEncoder 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']
]
testEncodingNil [
<category: 'testing'>
| enc ret |
enc := SoapSqEncoder new.
ret := enc encodeSoapVariable: (SoapVariable name: 'auau' value: nil).
self should: [ret name = 'auau'].
self should: [(ret getAttributeNamed: 'xsi:null') = 1].
self should: [ret isEmptyBody]
]
testEncodingObject [
<category: 'testing'>
| enc obj ret byteStr oStr val |
enc := SoapSqEncoder 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') = 'Squeak-ENC:ReferenceStream'].
byteStr := Base64MimeConverter
mimeDecodeToBytes: (ReadStream on: ret value).
oStr := SmartRefStream on: byteStr.
val := oStr next.
self should: [obj = val]
]
testEncodingString [
<category: 'testing'>
| enc ret |
enc := SoapSqEncoder 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']
]
]
Object subclass: SoPortableTestUtil [
<category: 'SOAP-TestCases'>
<comment: nil>
SoPortableTestUtil class >> createHttpRequest [
<category: 'actions'>
| req |
req := HttpRequest new.
req header: (HttpParser parseHttpHeader: self httpRequestHeaderString).
req initStatusString: 'POST /SomeTarget HTTP/1.1'.
^req
]
SoPortableTestUtil class >> httpRequestFrom: aString [
"ToDo: Support other Smalltalks"
"##Squeak Comanche specific##"
<category: 'actions'>
^HttpRequest new header: (HttpParser parseHttpHeader: aString)
]
SoPortableTestUtil class >> httpRequestHeaderString [
<category: 'private'>
| crlfString |
crlfString := String with: Character cr with: Character lf.
^'POST /StockQuote HTTP/1.1' , crlfString
, 'Host: www.stockquoteserver.com' , crlfString
, 'Content-Type: text/xml; charset="utf-8"' , crlfString
, 'Content-Length: nnnn' , crlfString
, 'SOAPAction: "Some-URI"'
]
]
Object subclass: SoapHrefForDebug [
| target referenceDict realObject |
<category: 'SOAP-TestCases'>
<comment: 'This is provided for debugging SoapHref. Replace SoapHref with me when you encounter difficult bug in SoapHref.
'>
SoapHrefForDebug class >> on: target in: referenceDict [
<category: 'instance creation'>
^(self new)
target: target;
referenceDict: referenceDict;
yourself
]
basicInspect [
<category: 'actions'>
{self class.
{#target -> target.
#referenceDict -> referenceDict.
#realObject -> realObject}}
inspect
]
becomeReal [
<category: 'actions'>
realObject isNil ifFalse: [^self safeBecomeForward: realObject].
^self
]
doesNotUnderstand: aMessage [
<category: 'system primitives'>
| real |
real := self realObject.
(real isMemberOf: self class)
ifFalse: [^real perform: aMessage selector withArguments: aMessage arguments]
]
realObject [
<category: 'accessing'>
realObject
ifNil: [realObject := self referenceDict at: self target ifAbsent: [^self]].
^realObject
]
referenceDict [
"Answer the value of referenceDict"
<category: 'accessing'>
^referenceDict
]
referenceDict: anObject [
"Set the value of referenceDict"
<category: 'accessing'>
referenceDict := anObject
]
resolve [
<category: 'actions'>
self realObject
]
safeBecomeForward: anObject [
<category: 'private'>
anObject == true ifTrue: [^anObject].
anObject == false ifTrue: [^anObject].
anObject isNumber ifTrue: [^anObject].
anObject class isBits ifTrue: [^anObject].
anObject class isVariable ifTrue: [^anObject].
self becomeForward: anObject.
^self
]
target [
"Answer the value of target"
<category: 'accessing'>
^target
]
target: anObject [
"Set the value of target"
<category: 'accessing'>
| str |
str := anObject asString.
str ifEmpty: [^nil].
str := str copyFrom: 2 to: str size. "removing #"
target := str
]
yourself [
<category: 'actions'>
^self
resolve;
becomeReal
]
]
Object subclass: SoapMockServiceImpl [
<category: 'SOAP-TestCases'>
<comment: nil>
doSomething: arg1 [
<category: 'services'>
]
doSomething: arg1 with: arg2 [
<category: 'services'>
]
doSomething: arg1 with: arg2 with: arg3 [
<category: 'services'>
]
thisIsPrivate [
<category: 'private'>
]
]
Object subclass: SoapMockServiceImplForReferenceUsing [
<category: 'SOAP-TestCases'>
<comment: nil>
getAvailableLockers: clientTag postCode: postCode [
<category: 'actions'>
^
{clientTag.
postCode}
]
]