Mocketry willGenerateValueFrom: (was: Re: How do you mock http?)

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
7 messages Options
Reply | Threaded
Open this post in threaded view
|

Mocketry willGenerateValueFrom: (was: Re: How do you mock http?)

Herby Vojčík
Herby Vojčík wrote:

> Hello!
>
> I felt the need to mock http api (like nock in node, that is, mock http
> request-response itself on low-level part, leaving aside the question of
> what wrapper / library one uses to get to that http; in node it mocks
> basic http layer, here I tackled ZnClient), but struggled for a time how
> to grasp it. Finally I used something like this (with help of Mocketry,
> `1 to: 10` to mean "enough to actually be used even if there are more
> unrelated uses", it could as well be `1 to: 100`):
>
> ZnClient stub new willReturnValueFrom:
> ((1 to: 10) collect: [ :i | ZnMockClient

For Denis Kudriashov: would you be willing to add something like
`willGenerateValueFrom: aBlock` to Mocketry, so previous two lines could
be replaced by simpler:

   ZnClient stub new willGenerateValueFrom: [ ZnMockClient

?

If something allowing it is there, I am sorry but I haven't found it.

Herby

> whenRequest: [ :request |
> { request uri scheme. request uri authority. request uri
> pathPrintString. request uri query associations asSet }
> = { #https. 'onesignal.com'. '/api/v1/players/{1}' format: { UUID
> fromString36: 'Q7' }. { 'app_id' -> appId } asSet }
> and: [ #(GET HEAD) includes: request method ] ]
> thenResponse: [ :request | ZnResponse ok: (ZnEntity json: '{}') ] ]).
>
> with the help of this class (garbled utf not my fault, iceberg metacello
> integration does it):
>
> 'From Pharo6.0 of 13 May 2016 [Latest update: #60512] on 17 October 2017
> at 12:05:38.908634 pm'!
> ZnClient subclass: #ZnMockClient
> instanceVariableNames: 'conditionBlock responseBlock'
> classVariableNames: ''
> poolDictionaries: ''
> category: 'Towergame-Tests'!
> !ZnMockClient commentStamp: 'HerbyVojcik 10/16/2017 16:43' prior: 0!
> I am a mock ZnClient.
>
> I am created with ZnMockClient whenRequest: whenBlock thenResponse:
> thenBlock.
>
> Upon execution of the request, when (whenBlock cull: request) is true,
> response is set to (thenBlock cull: request). Otherwise, behaviour is
> delegated to super.!
>
>
> !ZnMockClient methodsFor: 'accessing' stamp: 'HerbertVojčík 10/17/2017
> 12:00:27'!
> conditionBlock
> ^ conditionBlock! !
>
> !ZnMockClient methodsFor: 'accessing' stamp: 'HerbertVojčík 10/17/2017
> 12:00:27'!
> responseBlock: anObject
> responseBlock := anObject! !
>
> !ZnMockClient methodsFor: 'accessing' stamp: 'HerbertVojčík 10/17/2017
> 12:00:27'!
> conditionBlock: anObject
> conditionBlock := anObject! !
>
> !ZnMockClient methodsFor: 'accessing' stamp: 'HerbertVojčík 10/17/2017
> 12:00:27'!
> responseBlock
> ^ responseBlock! !
>
>
> !ZnMockClient methodsFor: 'private protocol' stamp: 'HerbertVojčík
> 10/17/2017 12:00:27'!
> executeRequestResponse
> ^ (self conditionBlock cull: self request)
> ifTrue: [ response := self responseBlock cull: self request. response
> contents ]
> ifFalse: [ super executeRequestResponse ]! !
>
> "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
>
> ZnMockClient class
> instanceVariableNames: ''!
>
> !ZnMockClient class methodsFor: 'instance creation' stamp:
> 'HerbertVojčík 10/17/2017 12:00:27'!
> whenRequest: aBlock thenResponse: anotherBlock
> ^ self new
> conditionBlock: aBlock;
> responseBlock: anotherBlock;
> yourself! !
>
> Question 1: Is there a better way?
>
> Question 2: If not, would ZnMockClient be good addition to Zinc itself,
> to ease testing for others?
>
> Herby
>


Reply | Threaded
Open this post in threaded view
|

Re: Mocketry willGenerateValueFrom: (was: Re: How do you mock http?)

Denis Kudriashov
Hi Herby.

There is message #will: which accepts the block with possible arguments (if needed).

 ZnClient stub new will: [ ZnMockClient ...]

But generally your approach looks bad to me. You put too many details on your tests which just duplicate Zinc API used in the domain code. It makes tests brittle and tightly coupled. And they looks quite unreadable.

I usually introduce kind of MyExternalClient intermediate which provides normal messages to interact with remote system.  And it completely hides overall http communication.
So in tests I stub this guy with simple mocks. 
But in addition I write real communication tests specifically for that object. They can be unstable because it is real network. But idea to test actual communication in single place and abstract the rest of system from it. Also it provide good checker for the possible API changes and general problems with service. 

Best regards,
Denis


2017-10-17 12:34 GMT+02:00 Herby Vojčík <[hidden email]>:
Herby Vojčík wrote:
Hello!

I felt the need to mock http api (like nock in node, that is, mock http
request-response itself on low-level part, leaving aside the question of
what wrapper / library one uses to get to that http; in node it mocks
basic http layer, here I tackled ZnClient), but struggled for a time how
to grasp it. Finally I used something like this (with help of Mocketry,
`1 to: 10` to mean "enough to actually be used even if there are more
unrelated uses", it could as well be `1 to: 100`):

ZnClient stub new willReturnValueFrom:
((1 to: 10) collect: [ :i | ZnMockClient

For Denis Kudriashov: would you be willing to add something like `willGenerateValueFrom: aBlock` to Mocketry, so previous two lines could be replaced by simpler:

  ZnClient stub new willGenerateValueFrom: [ ZnMockClient

?

If something allowing it is there, I am sorry but I haven't found it.

Herby

whenRequest: [ :request |
{ request uri scheme. request uri authority. request uri
pathPrintString. request uri query associations asSet }
= { #https. 'onesignal.com'. '/api/v1/players/{1}' format: { UUID
fromString36: 'Q7' }. { 'app_id' -> appId } asSet }
and: [ #(GET HEAD) includes: request method ] ]
thenResponse: [ :request | ZnResponse ok: (ZnEntity json: '{}') ] ]).

with the help of this class (garbled utf not my fault, iceberg metacello
integration does it):

'From Pharo6.0 of 13 May 2016 [Latest update: #60512] on 17 October 2017
at 12:05:38.908634 pm'!
ZnClient subclass: #ZnMockClient
instanceVariableNames: 'conditionBlock responseBlock'
classVariableNames: ''
poolDictionaries: ''
category: 'Towergame-Tests'!
!ZnMockClient commentStamp: 'HerbyVojcik 10/16/2017 16:43' prior: 0!
I am a mock ZnClient.

I am created with ZnMockClient whenRequest: whenBlock thenResponse:
thenBlock.

Upon execution of the request, when (whenBlock cull: request) is true,
response is set to (thenBlock cull: request). Otherwise, behaviour is
delegated to super.!


!ZnMockClient methodsFor: 'accessing' stamp: 'HerbertVojÄ Ã­k 10/17/2017
12:00:27'!
conditionBlock
^ conditionBlock! !

!ZnMockClient methodsFor: 'accessing' stamp: 'HerbertVojÄ Ã­k 10/17/2017
12:00:27'!
responseBlock: anObject
responseBlock := anObject! !

!ZnMockClient methodsFor: 'accessing' stamp: 'HerbertVojÄ Ã­k 10/17/2017
12:00:27'!
conditionBlock: anObject
conditionBlock := anObject! !

!ZnMockClient methodsFor: 'accessing' stamp: 'HerbertVojÄ Ã­k 10/17/2017
12:00:27'!
responseBlock
^ responseBlock! !


!ZnMockClient methodsFor: 'private protocol' stamp: 'HerbertVojÄ Ã­k
10/17/2017 12:00:27'!
executeRequestResponse
^ (self conditionBlock cull: self request)
ifTrue: [ response := self responseBlock cull: self request. response
contents ]
ifFalse: [ super executeRequestResponse ]! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

ZnMockClient class
instanceVariableNames: ''!

!ZnMockClient class methodsFor: 'instance creation' stamp:
'HerbertVojÄ Ã­k 10/17/2017 12:00:27'!
whenRequest: aBlock thenResponse: anotherBlock
^ self new
conditionBlock: aBlock;
responseBlock: anotherBlock;
yourself! !

Question 1: Is there a better way?

Question 2: If not, would ZnMockClient be good addition to Zinc itself,
to ease testing for others?

Herby



Reply | Threaded
Open this post in threaded view
|

Re: Mocketry willGenerateValueFrom: (was: Re: How do you mock http?)

Herby Vojčík
Denis Kudriashov wrote:
> Hi Herby.
>
> There is message #will: which accepts the block with possible arguments
> (if needed).
>
>   ZnClient stub new will: [ ZnMockClient ...]

Ah. I had the impression that will: only accepts the MockExpectedXxx
instance... will try. Thanks.

> But generally your approach looks bad to me. You put too many details on
> your tests which just duplicate Zinc API used in the domain code. It
> makes tests brittle and tightly coupled. And they looks quite unreadable.
>
> I usuallyintroduce kind of MyExternalClient intermediatewhich provides

Well, yes, like dao I use to communicate with database. I see, but...
there is always a but. If I am able to mock communication at lower
level, I do not specify which object / library / client must be used to
achieve that communication. I often find this a plus.

> normal messages to interact with remote system. And it completely hides
> overall http communication.
> So in tests I stub this guy with simple mocks.
> But in addition I write real communication tests specifically for that
> object. They can be unstable because it is real network. But idea to
> test actual communication in single place and abstract the rest of
> system from it. Also it provide good checker for the possible API
> changes and general problems with service.

I tend to move this way when there is more communication with outside
APIs (atm, I only have then one instance). And, as mentioned, I got used
to mock things at http level from node, where nock library is great way
to do these kinds of tests, so I got a slight bias to use 'mock at http
level' approach.

> Best regards,
> Denis

Thanks, Herby

> 2017-10-17 12:34 GMT+02:00 Herby Vojčík <[hidden email]
> <mailto:[hidden email]>>:
>
>     Herby Vojčík wrote:
>
>         Hello!
>
>         I felt the need to mock http api (like nock in node, that is,
>         mock http
>         request-response itself on low-level part, leaving aside the
>         question of
>         what wrapper / library one uses to get to that http; in node it
>         mocks
>         basic http layer, here I tackled ZnClient), but struggled for a
>         time how
>         to grasp it. Finally I used something like this (with help of
>         Mocketry,
>         `1 to: 10` to mean "enough to actually be used even if there are
>         more
>         unrelated uses", it could as well be `1 to: 100`):
>
>         ZnClient stub new willReturnValueFrom:
>         ((1 to: 10) collect: [ :i | ZnMockClient
>
>
>     For Denis Kudriashov: would you be willing to add something like
>     `willGenerateValueFrom: aBlock` to Mocketry, so previous two lines
>     could be replaced by simpler:
>
>        ZnClient stub new willGenerateValueFrom: [ ZnMockClient
>
>     ?
>
>     If something allowing it is there, I am sorry but I haven't found it.
>
>     Herby
>
>         whenRequest: [ :request |
>         { request uri scheme. request uri authority. request uri
>         pathPrintString. request uri query associations asSet }
>         = { #https. 'onesignal.com <http://onesignal.com>'.
>         '/api/v1/players/{1}' format: { UUID
>         fromString36: 'Q7' }. { 'app_id' -> appId } asSet }
>         and: [ #(GET HEAD) includes: request method ] ]
>         thenResponse: [ :request | ZnResponse ok: (ZnEntity json: '{}')
>         ] ]).
>
>         with the help of this class (garbled utf not my fault, iceberg
>         metacello
>         integration does it):
>
>         'From Pharo6.0 of 13 May 2016 [Latest update: #60512] on 17
>         October 2017
>         at 12:05:38.908634 pm'!
>         ZnClient subclass: #ZnMockClient
>         instanceVariableNames: 'conditionBlock responseBlock'
>         classVariableNames: ''
>         poolDictionaries: ''
>         category: 'Towergame-Tests'!
>         !ZnMockClient commentStamp: 'HerbyVojcik 10/16/2017 16:43' prior: 0!
>         I am a mock ZnClient.
>
>         I am created with ZnMockClient whenRequest: whenBlock thenResponse:
>         thenBlock.
>
>         Upon execution of the request, when (whenBlock cull: request) is
>         true,
>         response is set to (thenBlock cull: request). Otherwise,
>         behaviour is
>         delegated to super.!
>
>
>         !ZnMockClient methodsFor: 'accessing' stamp: 'HerbertVojÄ Ã­k
>         10/17/2017
>         12:00:27'!
>         conditionBlock
>         ^ conditionBlock! !
>
>         !ZnMockClient methodsFor: 'accessing' stamp: 'HerbertVojÄ Ã­k
>         10/17/2017
>         12:00:27'!
>         responseBlock: anObject
>         responseBlock := anObject! !
>
>         !ZnMockClient methodsFor: 'accessing' stamp: 'HerbertVojÄ Ã­k
>         10/17/2017
>         12:00:27'!
>         conditionBlock: anObject
>         conditionBlock := anObject! !
>
>         !ZnMockClient methodsFor: 'accessing' stamp: 'HerbertVojÄ Ã­k
>         10/17/2017
>         12:00:27'!
>         responseBlock
>         ^ responseBlock! !
>
>
>         !ZnMockClient methodsFor: 'private protocol' stamp: 'HerbertVojÄ Ã­k
>         10/17/2017 12:00:27'!
>         executeRequestResponse
>         ^ (self conditionBlock cull: self request)
>         ifTrue: [ response := self responseBlock cull: self request.
>         response
>         contents ]
>         ifFalse: [ super executeRequestResponse ]! !
>
>         "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
>
>         ZnMockClient class
>         instanceVariableNames: ''!
>
>         !ZnMockClient class methodsFor: 'instance creation' stamp:
>         'HerbertVojÄ Ã­k 10/17/2017 12:00:27'!
>         whenRequest: aBlock thenResponse: anotherBlock
>         ^ self new
>         conditionBlock: aBlock;
>         responseBlock: anotherBlock;
>         yourself! !
>
>         Question 1: Is there a better way?
>
>         Question 2: If not, would ZnMockClient be good addition to Zinc
>         itself,
>         to ease testing for others?
>
>         Herby
>
>
>


Reply | Threaded
Open this post in threaded view
|

Re: Mocketry willGenerateValueFrom: (was: Re: How do you mock http?)

Herby Vojčík
In reply to this post by Denis Kudriashov
Denis Kudriashov wrote:

> Hi Herby.
>
> There is message #will: which accepts the block with possible arguments
> (if needed).
>
>   ZnClient stub new will: [ ZnMockClient ...]
>
> But generally your approach looks bad to me. You put too many details on
> your tests which just duplicate Zinc API used in the domain code. It
> makes tests brittle and tightly coupled. And they looks quite unreadable.

BTW, made it shorter and probably more readable as a result (by also
shortening the test condition):

   ZnClient stub new will: [ ZnMockClient
     whenRequest: [ :request |
       request uri =
('https://onesignal.com/api/v1/players/{1}?app_id={2}' format: { self
uidy: 'Q7'. appId }) asZnUrl
         and: [ #(GET HEAD) includes: request method ] ]
     thenResponse: [ :request | ZnResponse ok: (ZnEntity json: '{}') ] ].

The reason why I could not test uri as is, is Zinc adding ':443' to it.
But as mentioned, the previous was very unreadable; with asZnUrl it is
probably better.

Herby

Reply | Threaded
Open this post in threaded view
|

Re: Mocketry willGenerateValueFrom: (was: Re: How do you mock http?)

Denis Kudriashov
I would hide the tricks even more:

  ZnClient stubRequests: [ :request |
      request uri = ('https://onesignal.com/api/v1/players/{1}?app_id={2}' format: { self uidy: 'Q7'. appId }) asZnUrl
        and: [ #(GET HEAD) includes: request method ] ]
    byResponse: [ :request | ZnResponse ok: (ZnEntity json: '{}') ] ].

And maybe with set of more simple cases:

  ZnClient 
    stubGET: ('https://onesignal.com/api/v1/players/{1}?app_id={2}' format: { self uidy: 'Q7'. appId }) asZnUrl
    byResponse: [ :request | ZnResponse ok: (ZnEntity json: '{}') ] ]. 

Or better:

  ZnClient 
    stubGET: ('https://onesignal.com/api/v1/players' asZnUrl / (self uidy: 'Q7') 
    withParams: {'app_id' -> appId }
    byResponse: [ :request | ZnResponse ok: (ZnEntity json: '{}') ] ]. 



2017-10-17 14:22 GMT+02:00 Herby Vojčík <[hidden email]>:
Denis Kudriashov wrote:
Hi Herby.

There is message #will: which accepts the block with possible arguments
(if needed).

  ZnClient stub new will: [ ZnMockClient ...]

But generally your approach looks bad to me. You put too many details on
your tests which just duplicate Zinc API used in the domain code. It
makes tests brittle and tightly coupled. And they looks quite unreadable.

BTW, made it shorter and probably more readable as a result (by also shortening the test condition):

  ZnClient stub new will: [ ZnMockClient
    whenRequest: [ :request |
      request uri = ('https://onesignal.com/api/v1/players/{1}?app_id={2}' format: { self uidy: 'Q7'. appId }) asZnUrl
        and: [ #(GET HEAD) includes: request method ] ]
    thenResponse: [ :request | ZnResponse ok: (ZnEntity json: '{}') ] ].

The reason why I could not test uri as is, is Zinc adding ':443' to it. But as mentioned, the previous was very unreadable; with asZnUrl it is probably better.

Herby

Reply | Threaded
Open this post in threaded view
|

Re: Mocketry willGenerateValueFrom: (was: Re: How do you mock http?)

Herby Vojčík
Denis Kudriashov wrote:
> I would hide the tricks even more:
>
>    ZnClient stubRequests: [ :request |
>        request uri =
> ('https://onesignal.com/api/v1/players/{1}?app_id={2}
> <https://onesignal.com/api/v1/players/%7B1%7D?app_id=%7B2%7D>' format: {
> self uidy: 'Q7'. appId }) asZnUrl
>          and: [ #(GET HEAD) includes: request method ] ]
>      byResponse: [ :request | ZnResponse ok: (ZnEntity json: '{}') ] ].

This would be nice, but it would need cooperation of Zinc (unless I hide
mocketry use under extension method).

> And maybe with set of more simple cases:
>
>    ZnClient
>      stubGET: ('https://onesignal.com/api/v1/players/{1}?app_id={2}
> <https://onesignal.com/api/v1/players/%7B1%7D?app_id=%7B2%7D>' format: {
> self uidy: 'Q7'. appId }) asZnUrl
>      byResponse: [ :request | ZnResponse ok: (ZnEntity json: '{}') ] ].

Well, I actually send HEAD in production code, as I only need to know if
it is 2xx or 4xx (of course using #isSuccess and not testing status code
myself) and I want be nice. But GET is good as well. Now what? :-)

> Or better:
>
>    ZnClient
>      stubGET: ('https://onesignal.com/api/v1/players' asZnUrl / (self
> uidy: 'Q7')
>      withParams: {'app_id' -> appId }
>      byResponse: [ :request | ZnResponse ok: (ZnEntity json: '{}') ] ].

Yes, we're getting where nock library is on node. I didn't want to make
full http mocking dsl (would be nice, though). Actually asked if there
is one is the original thread. :-)

Herby

>
>
>
> 2017-10-17 14:22 GMT+02:00 Herby Vojčík <[hidden email]
> <mailto:[hidden email]>>:
>
>     Denis Kudriashov wrote:
>
>         Hi Herby.
>
>         There is message #will: which accepts the block with possible
>         arguments
>         (if needed).
>
>            ZnClient stub new will: [ ZnMockClient ...]
>
>         But generally your approach looks bad to me. You put too many
>         details on
>         your tests which just duplicate Zinc API used in the domain code. It
>         makes tests brittle and tightly coupled. And they looks quite
>         unreadable.
>
>
>     BTW, made it shorter and probably more readable as a result (by also
>     shortening the test condition):
>
>        ZnClient stub new will: [ ZnMockClient
>          whenRequest: [ :request |
>            request uri =
>     ('https://onesignal.com/api/v1/players/{1}?app_id={2}
>     <https://onesignal.com/api/v1/players/%7B1%7D?app_id=%7B2%7D>'
>     format: { self uidy: 'Q7'. appId }) asZnUrl
>              and: [ #(GET HEAD) includes: request method ] ]
>          thenResponse: [ :request | ZnResponse ok: (ZnEntity json: '{}')
>     ] ].
>
>     The reason why I could not test uri as is, is Zinc adding ':443' to
>     it. But as mentioned, the previous was very unreadable; with asZnUrl
>     it is probably better.
>
>     Herby
>
>


Reply | Threaded
Open this post in threaded view
|

Re: Mocketry willGenerateValueFrom: (was: Re: How do you mock http?)

Denis Kudriashov

2017-10-17 14:49 GMT+02:00 Herby Vojčík <[hidden email]>:
Denis Kudriashov wrote:
I would hide the tricks even more:

   ZnClient stubRequests: [ :request |
       request uri =
('https://onesignal.com/api/v1/players/{1}?app_id={2}
<https://onesignal.com/api/v1/players/%7B1%7D?app_id=%7B2%7D>' format: {
self uidy: 'Q7'. appId }) asZnUrl
         and: [ #(GET HEAD) includes: request method ] ]
     byResponse: [ :request | ZnResponse ok: (ZnEntity json: '{}') ] ].

This would be nice, but it would need cooperation of Zinc (unless I hide mocketry use under extension method).

Why not? I think it could be a  good library. Try to publish it as is. Then people can contribute with their own cases. 
I remember other people looked for similar tool in past. So it could be good start.
 

And maybe with set of more simple cases:

   ZnClient
     stubGET: ('https://onesignal.com/api/v1/players/{1}?app_id={2}
<https://onesignal.com/api/v1/players/%7B1%7D?app_id=%7B2%7D>' format: {
self uidy: 'Q7'. appId }) asZnUrl
     byResponse: [ :request | ZnResponse ok: (ZnEntity json: '{}') ] ].

Well, I actually send HEAD in production code, as I only need to know if it is 2xx or 4xx (of course using #isSuccess and not testing status code myself) and I want be nice. But GET is good as well. Now what? :-)

Or better:

   ZnClient
     stubGET: ('https://onesignal.com/api/v1/players' asZnUrl / (self
uidy: 'Q7')
     withParams: {'app_id' -> appId }
     byResponse: [ :request | ZnResponse ok: (ZnEntity json: '{}') ] ].

Yes, we're getting where nock library is on node. I didn't want to make full http mocking dsl (would be nice, though).

You can be the man who starts the process :). Not necessary to implement full version.
 
Actually asked if there is one is the original thread. :-)

Herby




2017-10-17 14:22 GMT+02:00 Herby Vojčík <[hidden email]
<mailto:[hidden email]>>:

    Denis Kudriashov wrote:

        Hi Herby.

        There is message #will: which accepts the block with possible
        arguments
        (if needed).

           ZnClient stub new will: [ ZnMockClient ...]

        But generally your approach looks bad to me. You put too many
        details on
        your tests which just duplicate Zinc API used in the domain code. It
        makes tests brittle and tightly coupled. And they looks quite
        unreadable.


    BTW, made it shorter and probably more readable as a result (by also
    shortening the test condition):

       ZnClient stub new will: [ ZnMockClient
         whenRequest: [ :request |
           request uri =
    ('https://onesignal.com/api/v1/players/{1}?app_id={2}
    <https://onesignal.com/api/v1/players/%7B1%7D?app_id=%7B2%7D>'
    format: { self uidy: 'Q7'. appId }) asZnUrl
             and: [ #(GET HEAD) includes: request method ] ]
         thenResponse: [ :request | ZnResponse ok: (ZnEntity json: '{}')
    ] ].

    The reason why I could not test uri as is, is Zinc adding ':443' to
    it. But as mentioned, the previous was very unreadable; with asZnUrl
    it is probably better.

    Herby