1=head1 NAME
2
3Catalyst::Plugin::Server::XMLRPC -- Catalyst XMLRPC Server Plugin
4
5=head1 SYNOPSIS
6
7    package MyApp;
8    use Catalyst qw/Server Server::XMLRPC/;
9
10    package MyApp::Controller::Example;
11    use base 'Catalyst::Controller';
12
13    sub echo : XMLRPC {                     # available as: example.echo
14        my ( $self, $c, @args ) = @_;
15        $c->stash->{xmlrpc} = join ', ', @args;
16    }
17
18    sub ping : XMLRPCPath('/ping') {        # available as: ping
19        my ( $self, $c ) = @_;
20        $c->stash->{xmlrpc} = 'Pong';
21    }
22
23    sub world : XMLRPCRegex(/hello/) {      # available as: *hello*
24        my ($self, $c) = @_;
25        $c->stash->{xmlrpc} = 'World';
26    }
27
28    sub echo : XMLRPCLocal {                # available as: example.echo
29        my ( $self, $c, @args ) = @_;
30        $c->stash->{xmlrpc} = join ', ', @args;
31    }
32
33    sub ping : XMLRPCGlobal {               # available as: ping
34        my ( $self, $c ) = @_;
35        $c->stash->{xmlrpc} = 'Pong';
36    }
37
38=head1 DESCRIPTION
39
40XMLRPC Plugin for Catalyst which we tried to make compatible with the
41way Catalyst works with URLS. Main features are:
42
43=over 4
44
45=item * Split XMLRPC methodNames by STRING to find out Controller.
46
47=item * Single entrypoint for XMLRPC calls, like http://host.tld/rpc
48
49=item * DispatchTypes (attributes) which work much the same as Catalyst attrs
50
51=item * XMLRPC Parameter handling transparent to Catalyst parameter handling
52
53=back
54
55=head1 HOW IT WORKS
56
57The default behaviour will handle XMLRPC Requests sent to C</rpc> by creating
58an OBJECT containing XMLRPC specific parameters in C<< $c->req->xmlrpc >>.
59
60Directly after, it will find out the Path of the Action to dispatch to, by
61splitting methodName by C<.>:
62
63  methodName: hello.world
64  path      : /hello/world
65
66From this point, it will dispatch to '/hello/world' when it exists,
67like Catalyst Urls would do. What means: you will be able to set Regexes,
68Paths etc on subroutines to define the endpoint.
69
70We discuss these custom XMLRPC attributes below.
71
72When the request is dispatched, we will return $c->stash->{xmlrpc} to the
73xmlrpc client, or, when it is not available, it will return $c->stash to
74the client. There is also a way of defining $c->stash keys to be send back
75to the client.
76
77=head1 ATTRIBUTES
78
79You can mark any method in your Catalyst application as being
80available remotely by using one of the following attributes,
81which can be added to any existing attributes, except Private.
82Remember that one of the mentioned attributes below are automatically
83also Privates...
84
85=over 4
86
87=item XMLRPC
88
89Make this method accessible via XMLRPC, the same way as Local does
90when using catalyst by URL.
91
92The following example will be accessible by method C<< hello.world >>:
93
94  package Catalyst::Controller::Hello
95  sub world : XMLRPC {}
96
97=item XMLRPCLocal
98
99Identical version of attribute C<XMLRPC>
100
101=item XMLRPCGlobal
102
103Make this method accessible via XMLRPC, the same way as GLOBAL does
104when using catalyst by URL.
105
106The following example will be accessible by method C<< ping >>:
107
108  package Catalyst::Controller::Hello
109  sub ping : XMLRPCGlobal {}
110
111=item XMLRPCPath('/say/hello')
112
113Make this method accessible via XMLRPC, the same way as Path does
114when using catalyst by URL.
115
116The following example will be accessible by method C<< say.hello >>:
117
118  package Catalyst::Controller::Hello
119  sub hello : XMLRPCPath('/say/hello') {}
120
121=item XMLRPCRegex('foo')
122
123Make this method accessible via XMLRPC, the same way as Regex does
124when using catalyst by URL.
125
126The following example will be accessible by example methods:
127C<< a.foo.method >>
128C<< wedoofoohere >>
129C<< foo.getaround >>
130
131  package Catalyst::Controller::Hello
132  sub hello : XMLRPCPath('foo') {}
133
134=back
135
136=head1 ACCESSORS
137
138Once you've used the plugin, you'll have an $c->request->xmlrpc accessor
139which will return an C<Catalyst::Plugin::Server::XMLRPC> object.
140
141You can query this object as follows:
142
143=over 4
144
145=item $c->req->xmlrpc->is_xmlrpc_request
146
147Boolean indicating whether the current request has been initiated
148via XMLRPC
149
150=item $c->req->xmlrpc->config
151
152Returns a C<Catalyst::Plugin::Server::XMLRPC::Config> object. See the
153C<CONFIGURATION> below on how to use and configure it.
154
155=item $c->req->xmlrpc->body
156
157The body of the original XMLRPC call
158
159=item $c->req->xmlrpc->method
160
161The name of the original method called via XMLRPC
162
163=item $c->req->xmlrpc->args
164
165A list of parameters supplied by the XMLRPC call
166
167=item $c->req->xmlrpc->result_as_string
168
169The XML body that will be sent back to the XMLRPC client
170
171=item $c->req->xmlrpc->error
172
173Allows you to set xmlrpc fault code and message
174
175Example:
176
177  $c->req->xmlrpc->error( [ 401 => 'Unauthorized' ] )
178
179To return status code C<401> with message C<Unauthorized>
180
181The default is to return error code C<500> on error.
182
183=back
184
185=head1 Server Accessors
186
187The following accessors are always available, whether you're in a xmlrpc
188specific request or not
189
190=over 4
191
192=item $c->server->xmlrpc->list_methods
193
194Returns a HASHREF containing the available xmlrpc methods in Catalyst as
195a key, and the C<Catalyst::Action> object as a value.
196
197=back
198
199=head1 CATALYST REQUEST
200
201To make things transparent, we try to put XMLRPC params into the Request
202object of Catalyst. But first we will explain something about the XMLRPC
203specifications.
204
205A full draft of these specifications can be found on:
206C<http://www.xmlrpc.com/spec>
207
208In short, a xmlrpc-request consists of a methodName, like a subroutine
209name, and a list of parameters. This list of parameters may contain strings
210(STRING), arrays (LIST) and structs (HASH). Off course, these can be nested.
211
212=over 4
213
214=item $c->req->arguments
215
216We will put the list of arguments into $c->req->arguments, thisway you can
217fetch this list within your dispatched-to-subroutine:
218
219  sub echo : XMLRPC {
220      my ($self, $c, @args) = @_;
221      $c->log->debug($arg[0]);              # Prints first XMLRPC parameter
222                                            # to debug log
223  }
224
225=item $c->req->parameters
226
227Because XMLRPC parameters are a LIST, we can't B<just> fill
228$c->req->paremeters. To keep things transparent, we made an extra config
229option what tells the XMLRPC server we can assume the following conditions
230on all XMLRPC requests:
231- There is only one XMLRPC parameter
232- This XMLRPC parameter is a struct (HASH)
233
234We will put this STRUCT as key-value pairs into $c->req->parameters.
235
236=item $c->req->params
237
238Alias of $c->req->parameters
239
240=item $c->req->param
241
242Alias of $c->req->parameters
243
244=back
245
246=cut
247
248{   package Catalyst::Plugin::Server::XMLRPC;
249
250    use strict;
251    use warnings;
252    use attributes ();
253    use MRO::Compat;
254    use Data::Dumper;
255
256    my $ServerClass = 'Catalyst::Plugin::Server::XMLRPC::Backend';
257
258    ### only for development dumps!
259    my $Debug = 0;
260
261    ###
262    ### Catalyst loading and dispatching
263    ###
264
265    ### Loads our xmlrpc backend class in $c->server->xmlrpc
266    sub setup_engine {
267        my $class = shift;
268        $class->server->register_server(
269                    'xmlrpc' => $ServerClass->new($class)
270                );
271        $class->next::method(@_);
272    }
273
274    ### Will load our customized DispatchTypes into Catalyst
275    sub setup_dispatcher {
276        my $class = shift;
277
278        ### Load custom DispatchTypes
279        $class->next::method( @_ );
280        $class->dispatcher->preload_dispatch_types(
281            @{$class->dispatcher->preload_dispatch_types},
282            qw/ +Catalyst::Plugin::Server::XMLRPC::DispatchType::XMLRPCPath
283                +Catalyst::Plugin::Server::XMLRPC::DispatchType::XMLRPCRegex/
284        );
285
286        return $class;
287    }
288
289    ### Loads the xmlrpc-server object, redispatch to the method
290    sub prepare_action {
291        my $c = shift;
292        my @args = @_;
293
294        ### set up the accessor to hold an xmlrpc server instance
295        $c->req->register_server(
296            'xmlrpc' => Catalyst::Plugin::Server::XMLRPC::Request->new()
297        );
298
299        ### are we an xmlrpc call? check the path against a regex
300        my $path = $c->server->xmlrpc->config->path;
301        if( $c->req->path =~ /$path/) {
302
303            PREPARE: {
304                ### mark us as an xmlrpc request
305                $c->req->xmlrpc->is_xmlrpc_request(1);
306
307                $c->log->debug( 'PREPARE WITH $c ' . Dumper ($c ) ) if $Debug;
308
309                $c->req->xmlrpc->_deserialize_xml( $c ) or last PREPARE;
310
311                ### CAVEAT: we consider backing up to a default for a
312                ### xml-rpc method when the method doesn't exist a security
313                ### risk. So when the exact method doesn't exist, we return
314                ### an error.
315                ### TODO ARGH Because of regex methods, this won't work
316
317                ### set the new request path, the one we will forward to
318                $c->req->path( $c->req->xmlrpc->forward_path );
319
320                ### filter change dispatch types to our OWN
321                {   my $saved_dt = $c->dispatcher->dispatch_types || [];
322                    my $dp_ns
323                        = 'Catalyst::Plugin::Server::XMLRPC::DispatchType::';
324
325                    $c->dispatcher->dispatch_types(
326                        [ grep {
327                                $_->isa($dp_ns . 'XMLRPCPath')
328                                or
329                                $_->isa($dp_ns . 'XMLRPCRegex')
330                            } @$saved_dt
331                        ]
332                    );
333
334                    ### run the rest of the prepare actions, we should have
335                    ### an action object now
336                    $c->next::method( @_ );
337
338                    ### restore the saved dispatchtypes
339                    $c->dispatcher->dispatch_types( $saved_dt );
340                }
341
342                ### check if we have a c->action now
343                ### check if the NEW action isn't hte same as the
344                ### OLD action -- which mean no method was found
345                ### Not needed, don't have an action until we NEXT
346                if( (not $c->action) &&
347                    !$c->server->xmlrpc->private_methods->{
348                                                $c->req->xmlrpc->method
349                                            }
350                ) {
351                    $c->req->xmlrpc->_error(
352                        $c, 400, qq[Invalid XMLRPC request: No such method]
353                    );
354                    last PREPARE;
355                }
356            }
357
358            ### XMLRPC parameters and argument processing, see the Request
359            ### class below for information why we can't do it there.
360            $c->req->parameters( $c->req->xmlrpc->params )
361                        if $c->server->xmlrpc->config->convert_params;
362
363            $c->req->args($c->req->xmlrpc->args );
364
365        ### we're no xmlrpc request, so just let others handle it
366        } else {
367            $c->next::method( @_ );
368        }
369    }
370
371    ### before we dispatch, make sure no xmlrpc errors have happened already,
372    ### or an internal method has been called.
373    sub dispatch {
374        my $c = shift;
375
376        if( $c->req->xmlrpc->is_xmlrpc_request and
377            scalar( @{ $c->error } )
378        ) {
379            1;
380        } elsif (
381                $c->req->xmlrpc->is_xmlrpc_request and
382                $c->server->xmlrpc->private_methods->{$c->req->xmlrpc->method}
383        ) {
384                $c->req->xmlrpc->run_method($c);
385        } else {
386            $c->next::method( @_ );
387        }
388    }
389
390    sub finalize {
391        my $c = shift;
392
393        if( $c->req->xmlrpc->is_xmlrpc_request ) {
394
395            ### if we got an error anywhere, we'll return a fault
396            ### othwerise, the resultset will be returned
397            ### XXX TODO make error codes configurable ( done )
398            ### XXX TODO make messages customizable ( done )
399            my $res;
400            my $req_error = $c->req->xmlrpc->error;
401            if( scalar @{ $c->error } or $req_error ) {
402                if ($c->server->xmlrpc->config->show_errors) {
403                    if ( $req_error && ref $req_error eq 'ARRAY' ) {
404                         $res = RPC::XML::fault->new( @{ $req_error } );
405                    } else {
406                         $res = RPC::XML::fault->new( -1,
407                                join $/, @{ $c->error }
408                            );
409                    }
410                } else {
411                    if ( $req_error && ref $req_error eq 'ARRAY' ) {
412                        $res = RPC::XML::fault->new( @{ $req_error } );
413                    } else {
414                        $c->log->debug("XMLRPC 500 Errors:\n" .
415                                        join("\n", @{ $c->error })
416                                    );
417                        $res = RPC::XML::fault->new(
418                                            500,
419                                            'Internal Server Error'
420                                        );
421                    }
422                }
423            } else {
424                if( exists $c->stash->{xmlrpc} ) {
425                    $res = $c->stash->{xmlrpc};
426                } else {
427                    $res = $c->stash;
428                }
429            }
430
431            $c->res->body(
432                $c->req->xmlrpc->_serialize_xmlrpc( $c, $res )
433            );
434
435            ### make sure to clear the error, so catalyst doesn't try
436            ### to deal with it
437            $c->error( 0 );
438        }
439
440        $c->log->debug( 'FINALIZE ' . Dumper ( $c, \@_ ) )  if $Debug;
441
442        ### always call finalize at the end, so Catalyst's final handler
443        ### gets called as well
444        $c->next::method( @_ );
445    }
446}
447
448### The server implementation
449{   package Catalyst::Plugin::Server::XMLRPC::Backend;
450
451    use base qw/Class::Accessor::Fast/;
452    use Data::Dumper;
453    use Scalar::Util 'reftype';
454
455    __PACKAGE__->mk_accessors( qw/
456                                    dispatcher
457                                    private_methods
458                                    c
459                                    config
460                                /
461                            );
462
463    sub new {
464        my $class = shift;
465        my $c = shift;
466        my $self = $class->next::method( @_ );
467
468        $self->c($c);
469        $self->config( Catalyst::Plugin::Server::XMLRPC::Config->new( $c ) );
470        $self->private_methods({});
471        $self->dispatcher({});
472
473        ### Internal function
474        $self->add_private_method(
475            'system.listMethods' => sub {
476                my ($c_ob, @args) = @_;
477                return [ keys %{
478                    $c_ob->server->xmlrpc->list_methods;
479                    } ];
480            }
481        );
482
483        return $self;
484    }
485
486    sub add_private_method {
487        my ($self, $name, $sub) = @_;
488
489        return unless ($name && (reftype($sub) eq 'CODE'));
490        $self->private_methods->{$name} = $sub;
491        return 1;
492    }
493
494    sub list_methods {
495        my ($self) = @_;
496        return $self->dispatcher->{Path}->methods($self->c);
497    }
498}
499
500### the config implementation ###
501{   package Catalyst::Plugin::Server::XMLRPC::Config;
502    use base 'Class::Accessor::Fast';
503
504    ### XXX change me to an ENTRYPOINT!
505    my $DefaultPath     = qr!^(/?)rpc(/|$)!i;
506    my $DefaultAttr     = 'XMLRPC';
507    my $DefaultPrefix   = '';
508    my $DefaultSep      = '.';
509    my $DefaultShowErrors = 0;
510
511    ### XXX add: stash_fields (to encode) stash_exclude_fields (grep -v)
512
513    __PACKAGE__->mk_accessors(
514        qw/ path prefix separator attribute convert_params
515            show_errors xml_encoding allow_nil
516        /
517    );
518
519    ### return the cached version where possible
520    my $Obj;
521    sub new {
522        return $Obj if $Obj;
523
524        my $class = shift;
525        my $c     = shift;
526        my $self  = $class->next::method;
527
528        $self->prefix(   $c->config->{xmlrpc}->{prefix}    || $DefaultPrefix);
529        $self->separator($c->config->{xmlrpc}->{separator} || $DefaultSep);
530        $self->path(     $c->config->{xmlrpc}->{path}      || $DefaultPath);
531        $self->show_errors( $c->config->{xmlrpc}->{show_errors}
532                                || $DefaultShowErrors );
533        $self->xml_encoding( $c->config->{xmlrpc}->{xml_encoding} )
534                if $c->config->{xmlrpc}->{xml_encoding};
535        $self->allow_nil( $c->config->{xmlrpc}->{allow_nil} )
536                if $c->config->{xmlrpc}->{allow_nil};
537        $self->attribute($DefaultAttr);
538        $self->convert_params( 1 );
539
540        ### cache it
541        return $Obj = $self;
542    }
543}
544
545### the server class implementation ###
546{   package Catalyst::Plugin::Server::XMLRPC::Request;
547
548    use strict;
549    use warnings;
550
551    use RPC::XML;
552    use RPC::XML::Parser;
553    use Scalar::Util 'reftype';
554    use Clone::Fast qw/clone/;
555
556    use Data::Dumper;
557    use Text::SimpleTable;
558
559    use base 'Class::Data::Inheritable';
560    use base 'Class::Accessor::Fast';
561
562    __PACKAGE__->mk_accessors( qw[  forward_path args method body result
563                                    is_xmlrpc_request params
564                                    result_as_string internal_methods error
565                                ] );
566
567    __PACKAGE__->mk_classdata( qw[_xmlrpc_parser]);
568    __PACKAGE__->_xmlrpc_parser( RPC::XML::Parser->new );
569
570    *parameters = *params;
571
572    sub run_method {
573        my ($self, $c) = @_;
574
575        $c->stash->{xmlrpc} =
576            &{$c->server->xmlrpc->private_methods->{$self->method}}($c, @{ $c->req->args });
577    }
578
579    sub _deserialize_xml {
580        my ($self, $c) = @_;
581
582        ### the parser will die on failure, make sure we catch it
583        my $content; my $req;
584        eval {
585            ## Make sure we do not read from empty filehandle,
586            ## by sending empty string
587            $content = do { local $/; my $b = $c->req->body; $b ? <$b> : ''};
588            $req     = $self->_xmlrpc_parser->parse( $content );
589
590            ### RPC::XML::Parser *returns* the error string on error
591            ### OR an object... *sigh*
592            die $req unless ref $req;
593
594            ### Because we will die when request is not valid XMLRPC,
595            ### we simply test it. XXX TODO This results in a malformed
596            ### xml detected error, maybe we should catch it.
597            $req->name;
598            $req->args;
599        };
600
601        ### parsing the request went fine
602        if ( not $@ and defined $req->name ) {
603
604            $self->body( $content );                # original xml message
605            $self->method( $req->name );            # name of the method
606
607            ### allow the args to be encoded as a HASH when requested
608            ### xmlrpc only knows a top level 'list', and we can not tell
609            ### if that is meant to be a hash or not
610            ### make sure to store args as an ARRAY REF! to be compatible
611            ### with catalyst
612            my @args = map { $_->value } @{ $req->args };
613            $self->args( \@args );                  # parsed arguments
614
615            ### HEURISTIC! IF @args == 1 AND it's a HASHREF,
616            ### then we can assume it's key => value pairs in there
617            ### and we will map them to $c->req->params
618            $self->params(
619                (@args == 1 && (reftype($args[0]) eq 'HASH'))
620                    ? $args[0]
621                    : {}
622            );
623            ### build the relevant namespace, action and path
624            {   ### construct the forward path -- this allows catalyst to
625                ### do the hard work of dispatching for us
626                my $prefix  = $c->server->xmlrpc->config->prefix;
627                my ($sep)   = map { qr/$_/ }
628                              map { quotemeta $_ }
629                                        $c->server->xmlrpc->config->separator;
630
631                ### error checks here
632                if( $prefix =~ m|^/| ) {
633                    $c->log->debug( __PACKAGE__ . ": Your prefix starts with".
634                                    " a / -- This is not recommended"
635                                ) if $c->debug;
636                }
637
638                unless( ref($sep) eq 'Regexp' ) {
639                    $c->log->debug( __PACKAGE__ . ": Your separator is not a ".
640                                    "Regexp object -- This is not recommended"
641                                ) if $c->debug;
642                }
643
644                ### foo.bar => $prefix/foo/bar
645                ### DO NOT add a leading slash! uri.pm gets very upset
646                my @parts    = split( $sep, $self->method );
647                my $fwd_path = join '/',
648                                grep { defined && length } $prefix, @parts;
649
650
651                ### Complete our object-instance
652                $self->forward_path( $fwd_path );
653
654                ### Notify system of called rpc method and arguments
655                $c->log->debug('XML-RPC: Method called: ' . $self->method)
656                     if $c->debug;
657                if ($c->server->xmlrpc->config->convert_params &&
658                        $self->params
659                ) {
660                    my $params = Text::SimpleTable->new( [ 36, 'Key' ], [ 37, 'Value' ] );
661                    foreach my $key (sort keys %{$self->params}) {
662                        my $value = $self->params->{$key};
663                        $value = ref($value) || $value;
664                        $params->row($key, $value);
665                    }
666                    $c->log->debug("XML-RPC: Parameters:\n" . $params->draw)
667                                if ($c->debug && %{$self->params});
668                }
669            }
670
671        ### an error in parsing the request
672        } elsif ( $@ ) {
673            $self->_error( $c, 400, qq[Invalid XMLRPC request "$@"] );
674            return;
675
676        ### something is wrong, but who knows what...
677        } else {
678            $self->_error( $c, qq[Invalid XMLRPC request: Unknown error] );
679            return;
680        }
681
682        return $self;
683    }
684
685    ### alias arguments to args
686    *arguments = *args;
687
688    ### Serializes the response to $c->res->body
689    sub _serialize_xmlrpc {
690        my ( $self, $c, $status ) = @_;
691
692        local $RPC::XML::ENCODING = $c->server->xmlrpc->config->xml_encoding
693                if $c->server->xmlrpc->config->xml_encoding;
694
695        local $RPC::XML::ALLOW_NIL = $c->server->xmlrpc->config->allow_nil
696                if $c->server->xmlrpc->config->allow_nil;
697
698        local $Clone::Fast::BREAK_REFS = 1;
699
700        my $res = RPC::XML::response->new(clone($status));
701        $c->res->content_type('text/xml');
702
703        return $self->result_as_string( $res->as_string );
704    }
705
706    ### record errors in the error and debug log -- just for convenience
707    sub _error {
708        my($self, $c, $code, $msg) = @_;
709
710	($code, $msg) = (500, $code) unless defined $msg;
711        $c->log->debug( $msg ) if $c->debug;
712        $self->error( [ $code, $msg ] );
713    }
714}
715
716
7171;
718
719__END__
720
721=head1 INTERNAL XMLRPC FUNCTIONS
722
723The following system functions are available to the public.,
724
725=over 4
726
727=item system.listMethods
728
729returns a list of available RPC methods.
730
731=back
732
733=head1 DEFINING RETURN VALUES
734
735The XML-RPC response must contain a single parameter, which may contain
736an array (LIST), struct (HASH) or a string (STRING). To define the return
737values in your subroutine, you can alter $c->stash in three different ways.
738
739=head2 Defining $c->stash->{xmlrpc}
740
741When defining $c->stash->{xmlrpc}, the XMLRPC server will return these values
742to the client.
743
744=head2 When there is no $c->stash->{xmlrpc}
745
746When there is no C<< $c->stash->{xmlrpc} >> set, it will return the complete
747C<< $c->stash >>
748
749=head1 CONFIGURATION
750
751The XMLRPC Plugin accepts the following configuration options, which can
752be set in the standard Catalyst way (See C<perldoc Catalyst> for details):
753
754    Your::App->config( xmlrpc => { key => value } );
755
756You can look up any of the config parameters this package uses at runtime
757by calling:
758
759    $c->server->xmlrpc->config->KEY
760
761=over 4
762
763=item path
764
765This specifies the entry point for your xmlrpc server; all requests are
766dispatched from there. This is the url any XMLRCP client should post to.
767You can change this to any C<Regex> wish.
768
769The default is: C<qr!^(/?)rpc(/|$)!i>, which matches on a top-level path
770begining with C<rpc> preceeded or followed by an optional C</>, like this:
771
772    http://your-host.tld/rpc
773
774=item prefix
775
776This specifies the prefix of the forward url.
777
778For example, with a prefix of C<rpc>, and a method C<foo>, the forward
779path would be come C</rpc/foo>.
780
781The default is '' (empty).
782
783=item separator
784
785This is a STRING used to split your method on, allowing you to use
786a hierarchy in your method calls.
787
788For example, with a separator of C<.> the method call C<demo.echo>
789would be forwarded to C</demo/echo>.  To make C<demo_echo> forward to the
790same path, you would change the separator to C<_>,
791
792The default is C<.>, splitting methods on a single C<.>
793
794=item convert_params
795
796Make the arguments in C<< $c->req->xmlrpc->params >> available as
797C<< $c->req->params >>.
798
799Defaults to true.
800
801=item show_errors
802
803Make system errors in C<< $c->error >> public to the rpc-caller in a XML-RPC
804faultString. When show_errors is false, and your catalyst app generates a
805fault, it will return an XML-RPC fault containing error number 500 and error
806string: "Internal Server Error".
807
808Defaults to false.
809
810=item xml_encoding
811
812Change the xml encoding send over to the client. So you could change the
813default encoding to C<UTF-8> for instance.
814
815Defaults to C<us-ascii> which is the default of C<RPC::XML>.
816
817=item allow_nil
818
819Allow undefined values to be encoded as a C<< nil >> element of an empty
820string.
821
822Defaults to false which is the default of C<RPC::XML>.
823
824=back
825
826=head1 DIAGNOSTICS
827
828=over 4
829
830=item Invalid XMLRPC request: No such method
831
832There is no corresponding method in your application that can be
833forwarded to.
834
835=item Invalid XMLRPC request %s
836
837There was an error parsing the XMLRPC request
838
839=item Invalid XMLRPC request: Unknown error
840
841An unexpected error occurred
842
843=back
844
845=head1 TODO
846
847=over 4
848
849=item Make error messages configurable/filterable
850
851Right now, whatever ends up on $c->error gets returned to the client.
852It would be nice to have a way to filter/massage these messages before
853they are sent back to the client.
854
855=item Make stash filterable before returning
856
857Just like the error messages, it would be nice to be able to filter the
858stash before returning so you can filter out keys you don't want to
859return to the client, or just return a certain list of keys.
860This all to make transparent use of XMLRPC and web easier.
861
862=back
863
864=head1 SEE ALSO
865
866L<Catalyst::Plugin::Server::XMLRPC::Tutorial>, L<Catalyst::Manual>,
867L<Catalyst::Request>, L<Catalyst::Response>,  L<RPC::XML>,
868C<bin/rpc_client>
869
870=head1 ACKNOWLEDGEMENTS
871
872For the original implementation of this module:
873
874Marcus Ramberg, C<mramberg@cpan.org>
875Christian Hansen
876Yoshinori Sano
877
878=head1 AUTHORS
879
880Original Authors: Jos Boumans (kane@cpan.org) and Michiel Ootjers (michiel@cpan.org)
881
882Actually maintained by Jose Luis Martinez Torres JLMARTIN (jlmartinez@capside.com)
883
884=head1 THANKS
885
886Tomas Doran (BOBTFISH) for helping out with the debugging
887
888=head1 BUG REPORTS
889
890Please submit all bugs regarding C<Catalyst::Plugin::Server> to
891C<bug-catalyst-plugin-server@rt.cpan.org>
892
893=head1 LICENSE
894
895This library is free software, you can redistribute it and/or modify
896it under the same terms as Perl itself.
897
898=cut
899