1package POE::Component::Server::TCP;
2
3use strict;
4
5use vars qw($VERSION);
6$VERSION = '1.368'; # NOTE - Should be #.### (three decimal places)
7
8use Carp qw(carp croak);
9use Socket qw(INADDR_ANY inet_ntoa inet_aton AF_INET AF_UNIX PF_UNIX);
10use Errno qw(ECONNABORTED ECONNRESET);
11
12BEGIN {
13  # under perl-5.6.2 the warning "leaks" from the eval, while newer versions don't...
14  # it's due to Exporter.pm behaving differently, so we have to shut it up
15  no warnings 'redefine';
16  local *Carp::carp = sub { die @_ };
17
18  # Socket::GetAddrInfo provides getaddrinfo where earlier Perls' Socket don't.
19  eval { Socket->import('getaddrinfo') };
20  if ($@) {
21    # :newapi is legacy, but we include it to be sure in case the user has an old version of GAI
22    eval { require Socket::GetAddrInfo; Socket::GetAddrInfo->import( qw(:newapi getaddrinfo) ) };
23    if ($@) {
24      *getaddrinfo = sub { Carp::confess("Unable to use IPv6: Socket::GetAddrInfo not available") };
25    }
26  }
27}
28
29# Explicit use to import the parameter constants.
30use POE::Session;
31use POE::Driver::SysRW;
32use POE::Filter::Line;
33use POE::Wheel::ReadWrite;
34use POE::Wheel::SocketFactory;
35
36sub DEBUG () { 0 }
37
38# Create the server.  This is just a handy way to encapsulate
39# POE::Session->create().  Because the states are so small, it uses
40# real inline coderefs.
41
42sub new {
43  my $type = shift;
44
45  # Helper so we don't have to type it all day.  $mi is a name I call
46  # myself.
47  my $mi = $type . '->new()';
48
49  # If they give us lemons, tell them to make their own damn
50  # lemonade.
51  croak "$mi requires an even number of parameters" if (@_ & 1);
52  my %param = @_;
53
54  # Extract parameters.
55  my $alias   = delete $param{Alias};
56  my $address = delete $param{Address};
57  my $hname   = delete $param{Hostname};
58  my $port    = delete $param{Port};
59  my $domain  = delete($param{Domain}) || AF_INET;
60  my $concurrency = delete $param{Concurrency};
61
62  $port = 0 unless defined $port;
63
64  foreach (
65    qw(
66      Acceptor Error ClientInput
67      ClientPreConnect ClientConnected ClientDisconnected
68      ClientError ClientFlushed
69      ClientLow ClientHigh
70    )
71  ) {
72    croak "$_ must be a coderef"
73      if defined($param{$_}) and ref($param{$_}) ne 'CODE';
74  }
75
76  my $high_mark_level = delete $param{HighMark};
77  my $low_mark_level  = delete $param{LowMark};
78  my $high_event      = delete $param{ClientHigh};
79  my $low_event       = delete $param{ClientLow};
80
81  my $mark_param_count = (
82    grep { defined $_ }
83    ($high_mark_level, $low_mark_level, $high_event, $low_event)
84  );
85  if ($mark_param_count and $mark_param_count < 4) {
86    croak "If you use the Mark settings, you must define all four";
87  }
88
89  $high_event = sub { } unless defined $high_event;
90  $low_event  = sub { } unless defined $low_event;
91
92  my $accept_callback = delete $param{Acceptor};
93  my $error_callback  = delete $param{Error};
94
95  my $client_input    = delete $param{ClientInput};
96
97  # Acceptor and ClientInput are mutually exclusive.
98  croak "$mi needs either an Acceptor or a ClientInput but not both"
99    unless defined($accept_callback) xor defined($client_input);
100
101  # Make sure ClientXyz are accompanied by ClientInput.
102  unless (defined($client_input)) {
103    foreach (grep /^Client/, keys %param) {
104      croak "$_ not permitted without ClientInput";
105    }
106  }
107
108  my $client_pre_connect  = delete $param{ClientPreConnect};
109  my $client_connected    = delete $param{ClientConnected};
110  my $client_disconnected = delete $param{ClientDisconnected};
111  my $client_error        = delete $param{ClientError};
112  my $client_filter       = delete $param{ClientFilter};
113  my $client_infilter     = delete $param{ClientInputFilter};
114  my $client_outfilter    = delete $param{ClientOutputFilter};
115  my $client_flushed      = delete $param{ClientFlushed};
116  my $session_type        = delete $param{SessionType};
117  my $session_params      = delete $param{SessionParams};
118  my $server_started      = delete $param{Started};
119  my $server_stopped      = delete $param{Stopped};
120  my $listener_args       = delete $param{ListenerArgs};
121
122  $listener_args = [] unless defined $listener_args;
123  croak "ListenerArgs must be an array reference"
124    unless ref($listener_args) eq 'ARRAY';
125
126  if (exists $param{Args}) {
127    if (exists $param{ClientArgs}) {
128      carp "Args is deprecated, and ignored since ClientArgs is present";
129      delete $param{Args};
130    }
131    else {
132      carp "Args is deprecated but allowed for now.  Please use ClientArgs";
133    }
134  }
135
136  my $client_args = delete($param{ClientArgs}) || delete($param{Args});
137
138  if ( (defined $client_infilter and ! defined $client_outfilter) or
139    (defined $client_outfilter and ! defined $client_infilter) ) {
140    croak "ClientInputFilter must be used with ClientOutputFilter";
141  }
142
143  if (defined $client_filter and defined $client_infilter) {
144    carp "ClientFilter ignored with ClientInputFilter and ClientOutputFilter";
145    undef $client_filter;
146  }
147
148  # Defaults.
149
150  $concurrency = -1 unless defined $concurrency;
151  my $accept_session_id;
152
153  if (!defined $address && defined $hname) {
154    $address = inet_aton($hname);
155  }
156  $address = INADDR_ANY unless defined $address;
157
158  $error_callback = \&_default_server_error unless defined $error_callback;
159
160  $session_type = 'POE::Session' unless defined $session_type;
161  if (defined($session_params) && ref($session_params)) {
162    if (ref($session_params) ne 'ARRAY') {
163      croak "SessionParams must be an array reference";
164    }
165  } else {
166    $session_params = [ ];
167  }
168
169  if (defined $client_input) {
170    $client_error  = \&_default_client_error unless defined $client_error;
171    $client_args         = []     unless defined $client_args;
172
173    # Extra states.
174
175    my $inline_states = delete $param{InlineStates};
176    $inline_states = {} unless defined $inline_states;
177
178    my $package_states = delete $param{PackageStates};
179    $package_states = [] unless defined $package_states;
180
181    my $object_states = delete $param{ObjectStates};
182    $object_states = [] unless defined $object_states;
183
184    my $shutdown_on_error = 1;
185    if (exists $param{ClientShutdownOnError}) {
186      $shutdown_on_error = delete $param{ClientShutdownOnError};
187    }
188
189    croak "InlineStates must be a hash reference"
190      unless ref($inline_states) eq 'HASH';
191
192    croak "PackageStates must be a list or array reference"
193      unless ref($package_states) eq 'ARRAY';
194
195    croak "ObjectsStates must be a list or array reference"
196      unless ref($object_states) eq 'ARRAY';
197
198    croak "ClientArgs must be an array reference"
199      unless ref($client_args) eq 'ARRAY';
200
201    # Sanity check, thanks to crab@irc for making this mistake, ha!
202    # TODO we could move this to POE::Session and make it a
203    # "sanity checking" sub somehow...
204    if (POE::Kernel::ASSERT_USAGE) {
205      my %forbidden_handlers = (
206        _child => 1,
207        _start => 1,
208        _stop => 1,
209        shutdown => 1,
210        tcp_server_got_error => 1,
211        tcp_server_got_flush => 1,
212        tcp_server_got_high => 1,
213        tcp_server_got_input => 1,
214        tcp_server_got_low => 1,
215      );
216
217      if (
218        my @forbidden_inline_handlers = (
219          grep { exists $inline_states->{$_} }
220          keys %forbidden_handlers
221        )
222      ) {
223        croak "These InlineStates aren't allowed: @forbidden_inline_handlers";
224      }
225
226      my %handlers = (
227        PackageStates => $package_states,
228        ObjectStates => $object_states,
229      );
230
231      while (my ($name, $states) = each(%handlers)) {
232        my %states_hash = @$states;
233        my @forbidden_handlers;
234        while (my ($package, $handlers) = each %states_hash) {
235          croak "Undefined $name member for $package" unless (
236            defined $handlers
237          );
238
239          if (ref($handlers) eq 'HASH') {
240            push(
241              @forbidden_handlers,
242              grep { exists $handlers->{$_} }
243              keys %forbidden_handlers
244            );
245          }
246          elsif (ref($handlers) eq 'ARRAY') {
247            push(
248              @forbidden_handlers,
249              grep { exists $forbidden_handlers{$_} }
250              @$handlers
251            );
252          }
253          else {
254            croak "Unknown $name member type for $package";
255          }
256        }
257
258        croak "These $name aren't allowed: @forbidden_handlers" if (
259          @forbidden_handlers
260        );
261      }
262    }
263
264    # Revise the acceptor callback so it spawns a session.
265
266    unless (defined $accept_callback) {
267      $accept_callback = sub {
268        my ($socket, $remote_addr, $remote_port) = @_[ARG0, ARG1, ARG2];
269
270        $session_type->create(
271          @$session_params,
272          inline_states => {
273            _start => sub {
274              my ( $kernel, $session, $heap ) = @_[KERNEL, SESSION, HEAP];
275
276              $heap->{shutdown} = 0;
277              $heap->{shutdown_on_error} = $shutdown_on_error;
278
279              # Unofficial UNIX support, suggested by Damir Dzeko.
280              # Real UNIX socket support should go into a separate
281              # module, but if that module only differs by four
282              # lines of code it would be bad to maintain two
283              # modules for the price of one.  One solution would be
284              # to pull most of this into a base class and derive
285              # TCP and UNIX versions from that.
286              if (
287                $domain == AF_UNIX or $domain == PF_UNIX
288              ) {
289                $heap->{remote_ip} = "LOCAL";
290              }
291              elsif (length($remote_addr) == 4) {
292                $heap->{remote_ip} = inet_ntoa($remote_addr);
293              }
294              else {
295                $heap->{remote_ip} = ( getaddrinfo($remote_addr) )[1];
296              }
297
298              $heap->{remote_port} = $remote_port;
299
300              my $socket = $_[ARG0];
301              if ($client_pre_connect) {
302                $socket = $client_pre_connect->(@_);
303                unless (defined($socket) and ref($socket) and fileno($socket)) {
304                  # TODO - The user ought to know what's going on
305                  # here, since it's triggered by something their
306                  # callback has done.  Should we expose a callback
307                  # anyway to avoid potential confusion?
308                  return;
309                }
310              }
311
312              $heap->{client} = POE::Wheel::ReadWrite->new(
313                Handle       => $socket,
314                Driver       => POE::Driver::SysRW->new(),
315                _get_filters(
316                  $client_filter,
317                  $client_infilter,
318                  $client_outfilter
319                ),
320                InputEvent   => 'tcp_server_got_input',
321                ErrorEvent   => 'tcp_server_got_error',
322                FlushedEvent => 'tcp_server_got_flush',
323
324                (
325                  $mark_param_count
326                  ? (
327                    HighMark  => $high_mark_level,
328                    HighEvent => 'tcp_server_got_high',
329                    LowMark   => $low_mark_level,
330                    LowEvent  => 'tcp_server_got_low',
331                  )
332                  : ()
333                ),
334              );
335
336              # Expand the Args constructor array, and place a copy
337              # into @_[ARG0..].  There are only 2 parameters.
338              splice(@_, ARG0, 2, @{$_[ARG1]});
339
340              $client_connected and $client_connected->(@_);
341            },
342            tcp_server_got_high => $high_event,
343            tcp_server_got_low => $low_event,
344
345            # To quiet ASSERT_STATES.
346            _child  => sub { },
347
348            tcp_server_got_input => sub {
349              return if $_[HEAP]->{shutdown};
350              $client_input->(@_);
351              undef;
352            },
353            tcp_server_got_error => sub {
354              DEBUG and warn(
355                "$$: $alias child Error ARG0=$_[ARG0] ARG1=$_[ARG1]"
356              );
357              unless ($_[ARG0] eq 'accept' and $_[ARG1] == ECONNABORTED) {
358                $client_error->(@_);
359                if ($_[HEAP]->{shutdown_on_error}) {
360                  $_[HEAP]->{got_an_error} = 1;
361                  $_[KERNEL]->yield("shutdown");
362                }
363              }
364            },
365            tcp_server_got_flush => sub {
366              my $heap = $_[HEAP];
367              DEBUG and warn "$$: $alias child Flush";
368              $client_flushed and $client_flushed->(@_);
369              if ($heap->{shutdown}) {
370                DEBUG and warn "$$: $alias child Flush, callback";
371                $client_disconnected and $client_disconnected->(@_);
372                delete $heap->{client};
373              }
374            },
375            shutdown => sub {
376              DEBUG and warn "$$: $alias child Shutdown";
377              my $heap = $_[HEAP];
378              $heap->{shutdown} = 1;
379              if (defined $heap->{client}) {
380                if (
381                  $heap->{got_an_error} or
382                  not $heap->{client}->get_driver_out_octets()
383                ) {
384                  DEBUG and warn "$$: $alias child Shutdown, callback";
385                  $client_disconnected and $client_disconnected->(@_);
386                  delete $heap->{client};
387                }
388              }
389            },
390            _stop => sub {
391              ## concurrency on close
392              DEBUG and warn(
393                "$$: $alias _stop accept_session = $accept_session_id"
394              );
395              if( defined $accept_session_id ) {
396                $_[KERNEL]->call( $accept_session_id, 'disconnected' );
397              }
398              else {
399                # This means that the Server::TCP was shutdown before
400                # this connection closed.  So it doesn't really matter that
401                # we can't decrement the connection counter.
402                DEBUG and warn(
403                  "$$: $_[HEAP]->{alias} Disconnected from a connection ",
404                  "without POE::Component::Server::TCP parent"
405                );
406              }
407              return;
408            },
409
410            # User supplied states.
411            %$inline_states
412          },
413
414          # More user supplied states.
415          package_states => $package_states,
416          object_states  => $object_states,
417
418          # XXX - If you change the number of args here, also change
419          # the splice elsewhere.
420          args => [ $socket, $client_args ],
421        );
422      };
423    }
424  };
425
426  # Complain about strange things we're given.
427  foreach (sort keys %param) {
428    carp "$mi doesn't recognize \"$_\" as a parameter";
429  }
430
431  ## verify concurrency on accept
432  my $orig_accept_callback = $accept_callback;
433  $accept_callback = sub {
434    $_[HEAP]->{connections}++;
435    DEBUG and warn(
436      "$$: $_[HEAP]->{alias} Connection opened ",
437      "($_[HEAP]->{connections} open)"
438    );
439    if( $_[HEAP]->{concurrency} != -1 and $_[HEAP]->{listener} ) {
440      if( $_[HEAP]->{connections} >= $_[HEAP]->{concurrency} ) {
441        DEBUG and warn(
442          "$$: $_[HEAP]->{alias} Concurrent connection limit reached, ",
443          "pausing accept"
444        );
445        $_[HEAP]->{listener}->pause_accept()
446      }
447    }
448    $orig_accept_callback->(@_);
449  };
450
451  # Create the session, at long last.
452  # This is done inline so that closures can customize it.
453  # We save the accept session's ID to avoid self reference.
454
455  $accept_session_id = $session_type->create(
456    @$session_params,
457    inline_states => {
458      _start => sub {
459        if (defined $alias) {
460          $_[HEAP]->{alias} = $alias;
461          $_[KERNEL]->alias_set( $alias );
462        }
463
464        $_[HEAP]->{concurrency} = $concurrency;
465        $_[HEAP]->{connections} = 0;
466
467        $_[HEAP]->{listener} = POE::Wheel::SocketFactory->new(
468          ( ($domain == AF_UNIX or $domain == PF_UNIX)
469            ? ()
470            : ( BindPort => $port )
471          ),
472          BindAddress  => $address,
473          SocketDomain => $domain,
474          Reuse        => 'yes',
475          SuccessEvent => 'tcp_server_got_connection',
476          FailureEvent => 'tcp_server_got_error',
477        );
478        $server_started and $server_started->(@_);
479      },
480      # Catch an error.
481      tcp_server_got_error => $error_callback,
482
483      # We accepted a connection.  Do something with it.
484      tcp_server_got_connection => $accept_callback,
485
486      # concurrency on close.
487      disconnected => sub {
488        $_[HEAP]->{connections}--;
489        DEBUG and warn(
490          "$$: $_[HEAP]->{alias} Connection closed ",
491          "($_[HEAP]->{connections} open)"
492        );
493        if ($_[HEAP]->{connections} < 0) {
494          warn(
495            "Excessive 'disconnected' event ",
496            "from $_[CALLER_FILE] at line $_[CALLER_LINE]\n"
497          );
498          $_[HEAP]->{connections} = 0;
499        }
500        if( $_[HEAP]->{concurrency} != -1 and $_[HEAP]->{listener} ) {
501          if( $_[HEAP]->{connections} == ($_[HEAP]->{concurrency}-1) ) {
502            DEBUG and warn(
503              "$$: $_[HEAP]->{alias} Concurrent connection limit ",
504              "reestablished, resuming accept"
505            );
506            $_[HEAP]->{listener}->resume_accept();
507          }
508        }
509      },
510
511      set_concurrency => sub {
512        $_[HEAP]->{concurrency} = $_[ARG0];
513        DEBUG and warn(
514          "$$: $_[HEAP]->{alias} Concurrent connection ",
515          "limit = $_[HEAP]->{concurrency}"
516        );
517        if( $_[HEAP]->{concurrency} != -1 and $_[HEAP]->{listener} ) {
518          if( $_[HEAP]->{connections} >= $_[HEAP]->{concurrency} ) {
519            DEBUG and warn(
520              "$$: $_[HEAP]->{alias} Concurrent connection limit ",
521              "reached, pausing accept"
522            );
523            $_[HEAP]->{listener}->pause_accept()
524          }
525          else {
526            DEBUG and warn(
527              "$$: $_[HEAP]->{alias} Concurrent connection limit ",
528              "reestablished, resuming accept"
529            );
530            $_[HEAP]->{listener}->resume_accept();
531          }
532        }
533      },
534
535      # Shut down.
536      shutdown => sub {
537        delete $_[HEAP]->{listener};
538        $_[KERNEL]->alias_remove( $_[HEAP]->{alias} )
539          if defined $_[HEAP]->{alias};
540      },
541
542      # Dummy states to prevent warnings.
543      _stop   => sub {
544        DEBUG and warn "$$: $_[HEAP]->{alias} _stop";
545        $server_stopped and $server_stopped->(@_);
546        undef($accept_session_id);
547        return 0;
548      },
549      _child  => sub { },
550    },
551
552    args => $listener_args,
553  )->ID;
554
555  # Return the session ID.
556  return $accept_session_id;
557}
558
559sub _get_filters {
560    my ($client_filter, $client_infilter, $client_outfilter) = @_;
561    if (defined $client_infilter or defined $client_outfilter) {
562      return (
563        "InputFilter"  => _load_filter($client_infilter),
564        "OutputFilter" => _load_filter($client_outfilter)
565      );
566    }
567    elsif (defined $client_filter) {
568      return ( "Filter" => _load_filter($client_filter) );
569    }
570    else {
571      return ( Filter => POE::Filter::Line->new(), );
572    }
573
574}
575
576# Get something: either arrayref, ref, or string
577# Return filter
578sub _load_filter {
579    my $filter = shift;
580    if (ref ($filter) eq 'ARRAY') {
581        my @args = @$filter;
582        $filter = shift @args;
583        if ( _test_filter($filter) ){
584            return $filter->new(@args);
585        } else {
586            return POE::Filter::Line->new(@args);
587        }
588    }
589    elsif (ref $filter) {
590        return $filter->clone();
591    }
592    else {
593        if ( _test_filter($filter) ) {
594            return $filter->new();
595        } else {
596            return POE::Filter::Line->new();
597        }
598    }
599}
600
601# Test if a Filter can be loaded, return success or failure
602sub _test_filter {
603    my $filter = shift;
604    my $eval = eval {
605        (my $mod = $filter) =~ s!::!/!g;
606        require "$mod.pm";
607        1;
608    };
609    if (!$eval and $@) {
610        carp(
611          "Failed to load [$filter]\n" .
612          "Reason $@\nUsing default POE::Filter::Line "
613        );
614        return 0;
615    }
616    return 1;
617}
618
619# The default server error handler logs to STDERR and shuts down the
620# server.
621
622sub _default_server_error {
623  warn("$$: ".
624    'Server ', $_[SESSION]->ID,
625    " got $_[ARG0] error $_[ARG1] ($_[ARG2])\n"
626  );
627  delete $_[HEAP]->{listener};
628}
629
630# The default client error handler logs to STDERR
631
632sub _default_client_error {
633  my ($syscall, $errno, $error) = @_[ARG0..ARG2];
634  unless ($syscall eq "read" and ($errno == 0 or $errno == ECONNRESET)) {
635    $error = "(no error)" unless $errno;
636    warn("$$: ".
637      'Client session ', $_[SESSION]->ID,
638      " got $syscall error $errno ($error)\n"
639    );
640  }
641}
642
6431;
644
645__END__
646
647=head1 NAME
648
649POE::Component::Server::TCP - a simplified TCP server
650
651=head1 SYNOPSIS
652
653  #!perl
654
655  use warnings;
656  use strict;
657
658  use POE qw(Component::Server::TCP);
659
660  POE::Component::Server::TCP->new(
661    Port => 12345,
662    ClientConnected => sub {
663      print "got a connection from $_[HEAP]{remote_ip}\n";
664      $_[HEAP]{client}->put("Smile from the server!");
665    },
666    ClientInput => sub {
667      my $client_input = $_[ARG0];
668      $client_input =~ tr[a-zA-Z][n-za-mN-ZA-M];
669      $_[HEAP]{client}->put($client_input);
670    },
671  );
672
673  POE::Kernel->run;
674  exit;
675
676=head1 DESCRIPTION
677
678POE::Component::Server::TCP implements a generic multi-Session server.
679Simple services may be put together in a few lines of code.  For
680example, a server that echoes input back to the client:
681
682  use POE qw(Component::Server::TCP);
683  POE::Component::Server::TCP->new(
684    Port => 12345,
685    ClientInput => sub { $_[HEAP]{client}->put($_[ARG0]) },
686  );
687  POE::Kernel->run();
688
689=head2 Accepting Connections Yourself
690
691POE::Component::Server::TCP has a default mode where it accepts new
692connections and creates the sessions to handle them.  Programs can do
693this themselves by providing their own C<Acceptor> callbacks.  See
694L</Acceptor> for details.
695
696=head2 Master Listener Session
697
698At creation time, POE::Component::Server::TCP starts one POE::Session
699to listen for new connections.  The component's C<Alias> refers to
700this master session.
701
702If C<Acceptor> is specified, then it's up to that callback to deal
703with newly accepted sockets.  Its parameters are that of
704POE::Wheel::SocketFactory's C<SuccessEvent>.
705
706Otherwise, the default C<Acceptor> callback will start a new session
707to handle each connection.  These child sessions do not have their own
708aliases, but their C<ClientConnected> and C<ClientDisconnected>
709callbacks may be used to register and unregister the sessions with a
710shared namespace, such as a hash keyed on session IDs, or an object
711that manages such a hash.
712
713  my %client_namespace;
714
715  sub handle_client_connected {
716    my $client_session_id = $_[SESSION]->ID;
717    $client_namespace{$client_session_id} = \%anything;
718  }
719
720  sub handle_client_disconnected {
721    my $client_session_id = $_[SESSION]->ID;
722    $client_namespace{$client_session_id} = \%anything;
723  }
724
725The component's C<Started> callback is invoked at the end of the
726master session's start-up routine.  The @_[ARG0..$#_] parameters are
727set to a copy of the values in the server's C<ListenerArgs>
728constructor parameter.  The other parameters are standard for
729POE::Session's _start handlers.
730
731The component's C<Stopped> callback is invoked at the beginning of the
732master session's _stop routine. The parameters are standard for
733POE::Session's _stop handlers.
734
735The component's C<Error> callback is invoked when the server has a
736problem listening for connections.  C<Error> may also be called if the
737component's default acceptor has trouble accepting a connection.
738C<Error> receives the usual ones for L<POE::Wheel::SocketFactory/FailureEvent> and
739L<POE::Wheel::ReadWrite/ErrorEvent>.
740
741=head2 Default Child Connection Sessions
742
743If C<Acceptor> isn't specified, POE::Component::Server::TCP's default
744handler will start a new session for each new client connection.  As
745mentioned above, these child sessions have no aliases of their own,
746but they may set aliases or register themselves another way during
747their C<ClientConnected> and C<ClientDisconnected> callbacks.
748
749It can't be stressed enough that the following callbacks are executed
750within the context of dynamic child sessions---one per client
751connection---and not in the master listening session.  This has been a
752major point of confusion.  We welcome suggestions for making this
753clearer.
754
755=for comment
756TODO - Document some of the implications of having each connection
757handled by a separate session.
758
759The component's C<ClientInput> callback defines how child sessions
760will handle input from their clients.  Its parameters are that of
761POE::Wheel::ReadWrite's C<InputEvent>.
762
763As mentioned C<ClientConnected> is called at the end of the child
764session's C<_start> routine.  The C<ClientConneted> callback receives
765the same parameters as the client session's _start does.  The arrayref
766passed to the constructor's C<Args> parameter is flattened and
767included in C<ClientConnected>'s parameters as @_[ARG0..$#_].
768
769  sub handle_client_connected {
770    my @constructor_args = @_[ARG0..$#_];
771    ...
772  }
773
774C<ClientPreConnect> is called before C<ClientConnected>, and its
775purpose is to allow programs to reject connections or condition
776sockets before they're given to POE::Wheel::ReadWrite for management.
777
778The C<ClientPreConnect> handler is called with the client socket in
779$_[ARG0], and its return value is significant.  It must return a
780valid client socket if the connection is acceptable.  It must return
781undef to reject the connection.
782
783Most $_[HEAP] values are valid in the C<ClientPreConnect> handler.
784Obviously, $_[HEAP]{client} is not because that wheel hasn't been
785created yet.
786
787In the following example, the C<ClientPreConnect> handler returns the
788client socket after it has been upgraded to an SSL connection.
789
790  sub handle_client_pre_connect {
791
792    # Make sure the remote address and port are valid.
793    return undef unless validate(
794      $_[HEAP]{remote_ip}, $_[HEAP]{remote_port}
795    );
796
797    # SSLify the socket, which is in $_[ARG0].
798    my $socket = eval { Server_SSLify($_[ARG0]) };
799    return undef if $@;
800
801    # Return the SSL-ified socket.
802    return $socket;
803  }
804
805C<ClientDisconnected> is called when the client has disconnected,
806either because the remote socket endpoint has closed or the local
807endpoint has been closed by the server.  This doesn't mean the
808client's session has ended, but the session most likely will very
809shortly.  C<ClientDisconnected> is called from a couple disparate
810places within the component, so its parameters are neither consistent
811nor generally useful.
812
813C<ClientError> is called when an error has occurred on the socket.
814Its parameters are those of POE::Wheel::ReadWrite's C<ErrorEvent>.
815
816C<ClientFlushed> is called when all pending output has been flushed to
817the client socket.  Its parameters come from POE::Wheel::ReadWrite's
818C<ErrorEvent>.
819
820=head2 Performance Considerations
821
822This ease of use comes at a price: POE::Component::Server::TCP often
823performs significantly slower than a comparable server written with
824POE::Wheel::SocketFactory and POE::Wheel::ReadWrite.
825
826If performance is your primary goal, POE::Kernel's select_read() and
827select_write() perform about the same as IO::Select, but your code
828will be portable across every event loop POE supports.
829
830=head2 Special Needs Considerations
831
832POE::Component::Server::TCP is written to be easy for the most common
833use cases.  Programs with more special needs should consider using
834POE::Wheel::SocketFactory and POE::Wheel::ReadWrite instead.  These
835are lower-level modules, and using them requires more effort.  They
836are more flexible and customizable, however.
837
838=head1 PUBLIC METHODS
839
840=head2 new
841
842new() starts a server based on POE::Component::Server::TCP and returns
843a session ID for the master listening session.  All error handling is
844done within the server, via the C<Error> and C<ClientError> callbacks.
845
846The server may be shut down by posting a "shutdown" event to the
847master session, either by its ID or the name given to it by the
848C<Alias> parameter.
849
850POE::Component::Server::TCP does a lot of work in its constructor.
851The design goal is to push as much overhead into one-time construction
852so that ongoing run-time has less overhead.  Because of this, the
853server's constructor can take quite a daunting number of parameters.
854
855POE::Component::Server::TCP always returns a POE::Session ID for the
856session that will be listening for new connections.
857
858Many of the constructor parameters have been previously described.
859They are covered briefly again below.
860
861=head3 Server Session Configuration
862
863These constructor parameters affect POE::Component::Server::TCP's main
864listening session.
865
866=for comment
867TODO - Document the shutdown procedure somewhere.
868
869=head4 Acceptor
870
871C<Acceptor> defines a CODE reference that POE::Wheel::SocketFactory's
872C<SuccessEvent> will trigger to handle new connections.  Therefore the
873parameters passed to C<Acceptor> are identical to those given to
874C<SuccessEvent>.
875
876C<Acceptor> is optional; the default handler will create a new session
877for each connection.  All the "Client" constructor parameters are used
878to customize this session.  In other words, C<ClientInput> and such
879B<are not used when C<Acceptor> is set>.
880
881The default C<Acceptor> adds significant convenience and flexibility
882to POE::Component::Server::TCP, but it's not always a good fit for
883every application.  In some cases, a custom C<Acceptor> or even
884rolling one's own server with POE::Wheel::SocketFactory and
885POE::Wheel::ReadWrite may be better and/or faster.
886
887  Acceptor => sub {
888    my ($socket, $remote_address, $remote_port) = @_[ARG0..ARG2];
889    # Set up something to interact with the client.
890  }
891
892=head4 Address
893
894C<Address> defines a single interface address the server will bind to.
895It defaults to INADDR_ANY or INADDR6_ANY, when using IPv4 or IPv6,
896respectively.  It is often used with C<Port>.
897
898The value in C<Address> is passed to POE::Wheel::SocketFactory's
899C<BindAddress> parameter, so it may be in whatever form that module
900supports.  At the time of this writing, that may be a dotted IPv4
901quad, an IPv6 address, a host name, or a packed Internet address.  See
902also L</Hostname>.
903
904=for comment
905TODO - Example, using the lines below.
906
907  Address => '127.0.0.1'   # Localhost IPv4
908  Address => "::1"         # Localhost IPv6
909
910=head4 Alias
911
912C<Alias> is an optional name that will be given to the server's master
913listening session.  Events sent to this name will not be delivered to
914individual connections.
915
916The server's C<Alias> may be important if it's necessary to shut a
917server down.
918
919  sub sigusr1_handler {
920    $_[KERNEL]->post(chargen_server => 'shutdown');
921    $_[KERNEL]->sig_handled();
922  }
923
924=head4 Concurrency
925
926C<Concurrency> controls how many connections may be active at the same
927time.  It defaults to -1, which allows POE::Component::Server::TCP to
928accept concurrent connections until the process runs out of resources.
929
930Setting C<Concurrency> to 0 prevents the server from accepting new
931connections.  This may be useful if a server must perform lengthy
932initialization before allowing connections.  When the initialization
933finishes, it can yield(set_concurrency => -1) to enable connections.
934Likewise, a running server may yield(set_concurrency => 0) or any
935other number to dynamically tune its concurrency.  See L</EVENTS> for
936more about the set_concurrency event.
937
938Note: For C<Concurrency> to work with a custom C<Acceptor>, the
939server's listening session must receive a C<disconnected> event
940whenever clients disconnect.  Otherwise the listener cannot mediate
941between its connections.
942
943Example:
944
945  Acceptor => sub {
946    # ....
947    POE::Session->create(
948      # ....
949      inline_states => {
950        _start => sub {
951          # ....
952          # remember who our parent is
953          $_[HEAP]->{server_tcp} = $_[SENDER]->ID;
954          # ....
955        },
956        got_client_disconnect => sub {
957          # ....
958          $_[KERNEL]->post( $_[HEAP]->{server_tcp} => 'disconnected' );
959          # ....
960        }
961      }
962    );
963  }
964
965
966=head4 Domain
967
968C<Domain> sets the address or protocol family within which to operate.
969The C<Domain> may be any value that POE::Wheel::SocketFactory
970supports.  AF_INET (Internet address space) is used by default.
971
972Use AF_INET6 for IPv6 support.  This constant is exported by L<Socket>
973or L<Socket6>, depending on your version of Perl. Also be sure to have
974L<Socket::GetAddrInfo> installed, which is required by
975L<POE::Wheel::SocketFactory> for IPv6 support.
976
977=head4 Error
978
979C<Error> is the callback that will be invoked when the server socket
980reports an error.  The Error callback will be used to handle
981POE::Wheel::SocketFactory's FailureEvent, so it will receive the same
982parameters as discussed there.
983
984A default error handler will be provided if Error is omitted.  The
985default handler will log the error to STDERR and shut down the server.
986Active connections will be permitted to complete their transactions.
987
988  Error => sub {
989    my ($syscall_name, $err_num, $err_str) = @_[ARG0..ARG2];
990    # Handle the error.
991  }
992
993=head4 Hostname
994
995C<Hostname> is the optional non-packed name of the interface the TCP
996server will bind to.  The hostname will always be resolved via
997inet_aton() and so can either be a dotted quad or a name.  Name
998resolution is a one-time start-up action; there are no ongoing
999run-time penalties for using it.
1000
1001C<Hostname> guarantees name resolution, where C<Address> does not.
1002It's therefore preferred to use C<Hostname> in cases where resolution
1003must always be done.
1004
1005=head4 InlineStates
1006
1007C<InlineStates> is optional.  If specified, it must hold a hashref of
1008named callbacks.  Its syntax is that of POE:Session->create()'s
1009inline_states parameter.
1010
1011Remember: These InlineStates handlers will be added to the client
1012sessions, not to the main listening session.  A yield() in the listener
1013will not reach these handlers.
1014
1015If POE::Kernel::ASSERT_USAGE is enabled, the constructor will croak() if it
1016detects a state that it uses internally. For example, please use the "Started"
1017and "Stopped" callbacks if you want to specify your own "_start" and "_stop"
1018events respectively.
1019
1020=head4 ObjectStates
1021
1022If C<ObjectStates> is specified, it must holde an arrayref of objects
1023and the events they will handle.  The arrayref must follow the syntax
1024for POE::Session->create()'s object_states parameter.
1025
1026Remember: These ObjectStates handlers will be added to the client
1027sessions, not to the main listening session.  A yield() in the listener
1028will not reach these handlers.
1029
1030If POE::Kernel::ASSERT_USAGE is enabled, the constructor will croak() if it
1031detects a state that it uses internally. For example, please use the "Started"
1032and "Stopped" callbacks if you want to specify your own "_start" and "_stop"
1033events respectively.
1034
1035=head4 PackageStates
1036
1037When the optional C<PackageStates> is set, it must hold an arrayref of
1038package names and the events they will handle  The arrayref must
1039follow the syntax for POE::Session->create()'s package_states
1040parameter.
1041
1042Remember: These PackageStates handlers will be added to the client
1043sessions, not to the main listening session.  A yield() in the listener
1044will not reach these handlers.
1045
1046If POE::Kernel::ASSERT_USAGE is enabled, the constructor will croak() if it
1047detects a state that it uses internally. For example, please use the "Started"
1048and "Stopped" callbacks if you want to specify your own "_start" and "_stop"
1049events respectively.
1050
1051=head4 Port
1052
1053C<Port> contains the port the listening socket will be bound to.  It
1054defaults to 0, which usually lets the operating system pick a
1055port at random.
1056
1057  Port => 30023
1058
1059It is often used with C<Address>.
1060
1061=head4 Started
1062
1063C<Started> sets an optional callback that will be invoked within the
1064main server session's context.  It notifies the server that it has
1065fully started.  The callback's parameters are the usual for a
1066session's _start handler.
1067
1068=head4 Stopped
1069
1070C<Stopped> sets an optional callback that will be invoked within the
1071main server session's context.  It notifies the server that it has
1072fully stopped.  The callback's parameters are the usual for a
1073session's _stop handler.
1074
1075=head4 ListenerArgs
1076
1077C<ListenerArgs> is passed to the listener session as the C<args> parameter.  In
1078other words, it must be an arrayref, and the values are passed into the
1079C<Started> handler as ARG0, ARG1, etc.
1080
1081=head3 Connection Session Configuration
1082
1083These constructor parameters affect the individual sessions that
1084interact with established connections.
1085
1086=head4 ClientArgs
1087
1088C<ClientArgs> is optional.  When specified, it holds an ARRAYREF that
1089will be expanded one level and passed to the C<ClientConnected>
1090callback in @_[ARG0..$#_].
1091
1092=head4 ClientConnected
1093
1094Each new client connection is handled by a new POE::Session instance.
1095C<ClientConnected> is a callback that notifies the application when a
1096client's session is started and ready for operation.  Banners are
1097often sent to the remote client from this callback.
1098
1099The @_[ARG0..$#_] parameters to C<ClientConnected> are a copy of the
1100values in the C<ClientArgs> constructor parameter's array reference.
1101The other @_ members are standard for a POE::Session _start handler.
1102
1103C<ClientConnected> is called once per session start-up.  It will never
1104be called twice for the same connection.
1105
1106  ClientConnected => sub {
1107    $_[HEAP]{client}->put("Hello, client!");
1108    # Other client initialization here.
1109  },
1110
1111=head4 ClientDisconnected
1112
1113C<ClientDisconnected> is a callback that will be invoked when the
1114client disconnects or has been disconnected by the server.  It's
1115useful for cleaning up global client information, such as chat room
1116structures.  C<ClientDisconnected> callbacks receive the usual POE
1117parameters, but nothing special is included.
1118
1119  ClientDisconnected => sub {
1120    warn "Client disconnected"; # log it
1121  }
1122
1123=head4 ClientError
1124
1125The C<ClientError> callback is invoked when a client socket reports an
1126error.  C<ClientError> is called with POE's usual parameters, plus the
1127common error parameters: $_[ARG0] describes what was happening at the
1128time of failure.  $_[ARG1] and $_[ARG2] contain the numeric and string
1129versions of $!, respectively.
1130
1131C<ClientError> is optional.  If omitted, POE::Component::Server::TCP
1132will provide a default callback that logs most errors to STDERR.
1133
1134If C<ClientShutdownOnError> is set, the connection will be shut down
1135after C<ClientError> returns.  If C<ClientDisconnected> is specified,
1136it will be called as the client session is cleaned up.
1137
1138C<ClientError> is triggered by POE::Wheel::ReadWrite's ErrorEvent, so
1139it follows that event's form.  Please see the ErrorEvent documentation
1140in POE::Wheel::ReadWrite for more details.
1141
1142  ClientError => sub {
1143    my ($syscall_name, $error_num, $error_str) = @_[ARG0..ARG2];
1144    # Handle the client error here.
1145  }
1146
1147=head4 ClientFilter
1148
1149C<ClientFilter> specifies the POE::Filter object or class that will
1150parse input from each client and serialize output before it's sent to
1151each client.
1152
1153C<ClientFilter> may be a SCALAR, in which case it should name the
1154POE::Filter class to use.  Each new connection will be given a freshly
1155instantiated filter of that class.  No constructor parameters will be
1156passed.
1157
1158  ClientFilter => "POE::Filter::Stream",
1159
1160Some filters require constructor parameters.  These may be specified
1161by an ARRAYREF.  The first element is the POE::Filter class name, and
1162subsequent elements are passed to the class' constructor.
1163
1164  ClientFilter => [ "POE::Filter::Line", Literal => "\n" ],
1165
1166C<ClientFilter> may also be given an archetypical POE::Filter OBJECT.
1167In this case, each new client session will receive a clone() of the
1168given object.
1169
1170  ClientFilter => POE::Filter::Line->new(Literal => "\n"),
1171
1172C<ClientFilter> is optional.  The component will use
1173"POE::Filter::Line" if it is omitted.  There is L</ClientInputFilter>
1174and L</ClientOutputFilter> if you want to specify a different filter
1175for both directions.
1176
1177Filter modules are not automatically loaded.  Be sure that the program
1178loads the class before using it.
1179
1180=head4 ClientFlushed
1181
1182C<ClientFlushed> exposes POE::Wheel::ReadWrite's C<FlushedEvent> as a
1183callback.  It is called whenever the client's output buffer has been
1184fully flushed to the client socket.  At this point it's safe to shut
1185down the socket without losing data.
1186
1187C<ClientFlushed> is useful for streaming servers, where a "flushed"
1188event signals the need to send more data.
1189
1190  ClientFlushed => sub {
1191    my $data_source = $_[HEAP]{file_handle};
1192    my $read_count = sysread($data_source, my $buffer = "", 65536);
1193    if ($read_count) {
1194      $_[HEAP]{client}->put($buffer);
1195    }
1196    else {
1197      $_[KERNEL]->yield("shutdown");
1198    }
1199  },
1200
1201POE::Component::Server::TCP's default C<Acceptor> ensures that data is
1202flushed before finishing a client shutdown.
1203
1204=head4 ClientInput
1205
1206C<ClientInput> defines a per-connection callback to handle client
1207input.  This callback receives its parameters directly from
1208POE::Wheel::ReadWrite's C<InputEvent>.  ARG0 contains the input
1209record, the format of which is defined by C<ClientFilter> or
1210C<ClientInputFilter>.  ARG1 has the wheel's unique ID, and so on.
1211Please see POE:Wheel::ReadWrite for an in-depth description of
1212C<InputEvent>.
1213
1214C<ClientInput> and C<Acceptor> are mutually exclusive.  Enabling one
1215prohibits the other.
1216
1217  ClientInput => sub {
1218    my $input = $_[ARG0];
1219    $_[HEAP]{wheel}->put("You said: $input");
1220  },
1221
1222=head4 ClientInputFilter
1223
1224C<ClientInputFilter> is used with C<ClientOutputFilter> to specify
1225different protocols for input and output.  Both must be used together.
1226Both follow the same usage as L</ClientFilter>.  Overrides the filter set
1227by L</ClientFilter>.
1228
1229  ClientInputFilter  => [ "POE::Filter::Line", Literal => "\n" ],
1230  ClientOutputFilter => 'POE::Filter::Stream',
1231
1232=head4 ClientOutputFilter
1233
1234C<ClientOutputFilter> is used with C<ClientInputFilter> to specify
1235different protocols for input and output.  Both must be used together.
1236Both follow the same usage as L</ClientFilter>.  Overrides the filter set
1237by L</ClientFilter>.
1238
1239  ClientInputFilter  => POE::Filter::Line->new(Literal => "\n"),
1240  ClientOutputFilter => 'POE::Filter::Stream',
1241
1242=head4 ClientShutdownOnError
1243
1244C<ClientShutdownOnError> tells the component whether client
1245connections should be shut down automatically if an error is detected.
1246It defaults to "true".  Setting it to false (0, undef, "") turns off
1247this feature.
1248
1249The application is responsible for dealing with client errors if this
1250feature is disabled.  Not doing so may cause the component to emit a
1251constant stream of errors, eventually bogging down the application
1252with dead connections that spin out of control.
1253
1254Yes, this is terrible.  You have been warned.
1255
1256=head4 SessionParams
1257
1258C<SessionParams> specifies additional parameters that will be passed
1259to the C<SessionType> constructor at creation time.  It must be an
1260array reference.
1261
1262  SessionParams => [ options => { debug => 1, trace => 1 } ],
1263
1264Note: POE::Component::Server::TCP supplies its own POE::Session
1265constructor parameters.  Conflicts between them and C<SessionParams>
1266may cause the component to behave erratically.  To avoid such
1267problems, please limit SessionParams to the C<options> hash.  See
1268L<POE::Session> for an known options.
1269
1270We may enable other options later.  Please let us know if you need
1271something.
1272
1273=head4 SessionType
1274
1275C<SessionType> specifies the POE::Session subclass that will be
1276created for each new client connection.  "POE::Session" is the
1277default.
1278
1279  SessionType => "POE::Session::MultiDispatch"
1280
1281=head1 EVENTS
1282
1283It's possible to manipulate a TCP server component by sending it
1284messages.
1285
1286=head2 Main Server Commands
1287
1288These events must be sent to the main server, usually by the alias set
1289in its L<Alias> parameter.
1290
1291=head3 disconnected
1292
1293The "disconnected" event informs the TCP server that a connection was
1294closed.  It is needed when using L</Concurrency> with an L</Acceptor>
1295callback.  The custom Acceptor must provide its own disconnect
1296notification so that the server's connection counting logic works.
1297
1298Otherwise Concurrency clients will be accepted, and then no more.  The
1299server will never know when clients have disconnected.
1300
1301=head3 set_concurrency
1302
1303"set_concurrency" set the number of simultaneous connections the
1304server will be willing to accept.  See L</Concurrency> for more
1305details.  "set_concurrency" must have one parameter: the new maximum
1306connection count.
1307
1308  $kernel->call("my_server_alias", "set_concurrency", $max_count);
1309
1310=head3 shutdown
1311
1312The "shutdown" event starts a graceful server shutdown.  No new
1313connections will be accepted.  Existing connections will be allowed to
1314finish.  The server will be destroyed after the last connection ends.
1315
1316=head2 Per-Connection Commands
1317
1318These commands affect each client connection session.
1319
1320=head3 shutdown
1321
1322Sending "shutdown" to an individual client session instructs the
1323server to gracefully shut down that connection.  No new input will be
1324received, and any buffered output will be sent before the session
1325ends.
1326
1327Client sessions usually yield("shutdown") when they wish to disconnect
1328the client.
1329
1330  ClientInput => sub {
1331    if ($_[ARG0] eq "quit") {
1332      $_[HEAP]{client}->put("B'bye!");
1333      $_[KERNEL]->yield("shutdown");
1334      return;
1335    }
1336
1337    # Handle other input here.
1338  },
1339
1340=head1 Reserved HEAP Members
1341
1342Unlike most POE modules, POE::Component::Server::TCP stores data in
1343the client sessions' HEAPs.  These values are provided as conveniences
1344for application developers.
1345
1346=head2 HEAP Members for Master Listening Sessions
1347
1348The master listening session holds different data than client
1349connections.
1350
1351=head3 alias
1352
1353$_[HEAP]{alias} contains the server's Alias.
1354
1355=head3 concurrency
1356
1357$_[HEAP]{concurrency} remembers the server's C<Concurrency> parameter.
1358
1359=head3 connections
1360
1361$_[HEAP]{connections} is used to track the current number of
1362concurrent client connections.  It's incremented whenever a new
1363connection is accepted, and it's decremented whenever a client
1364disconnects.
1365
1366=head3 listener
1367
1368$_[HEAP]{listener} contains the POE::Wheel::SocketFactory object used
1369to listen for connections and accept them.
1370
1371=head2 HEAP Members for Connection Sessions
1372
1373These data members exist within the individual connections' sessions.
1374
1375=head3 client
1376
1377$_[HEAP]{client} contains a POE::Wheel::ReadWrite object used to
1378interact with the client.  All POE::Wheel::ReadWrite methods work.
1379
1380=head3 got_an_error
1381
1382$_[HEAP]{got_an_error} remembers whether the client connection has
1383already encountered an error.  It is part of the shutdown-on-error
1384procedure.
1385
1386=head3 remote_ip
1387
1388$_[HEAP]{remote_ip} contains the remote client's numeric address in
1389human-readable form.
1390
1391=head3 remote_port
1392
1393$_[HEAP]{remote_port} contains the remote client's numeric socket port
1394in human-readable form.
1395
1396=head3 remote_addr
1397
1398$_[HEAP]{remote_addr} contains the remote client's packed socket
1399address in computer-readable form.
1400
1401=head3 shutdown
1402
1403$_[HEAP]{shutdown} is true if the client is in the process of shutting
1404down.  The component uses it to ignore client input during shutdown,
1405and to close the connection after pending output has been flushed.
1406
1407=head3 shutdown_on_error
1408
1409$_[HEAP]{shutdown_on_error} remembers whether the client connection
1410should automatically shut down if an error occurs.
1411
1412=head1 SEE ALSO
1413
1414The SEE ALSO section in L<POE> contains a table of contents covering
1415the entire POE distribution.
1416
1417L<POE::Component::Client::TCP> is the client-side counterpart to this
1418module.
1419
1420This component uses and exposes features from L<POE::Filter>,
1421L<POE::Wheel::SocketFactory>, and L<POE::Wheel::ReadWrite>.
1422
1423=head1 BUGS
1424
1425This looks nothing like what Ann envisioned.
1426
1427This component currently does not accept many of the options that
1428POE::Wheel::SocketFactory does.
1429
1430This component will not bind to several addresses at once.  This may
1431be a limitation in SocketFactory, but it's not by design.
1432
1433This component needs better error handling.
1434
1435Some use cases require different session classes for the listener and
1436the connection handlers.  This isn't currently supported.  Please send
1437patches. :)
1438
1439=for comment
1440TODO - Document that Reuse is set implicitly.
1441
1442=head1 AUTHORS & COPYRIGHTS
1443
1444POE::Component::Server::TCP is Copyright 2000-2013 by Rocco Caputo.
1445All rights are reserved.  POE::Component::Server::TCP is free
1446software, and it may be redistributed and/or modified under the same
1447terms as Perl itself.
1448
1449POE::Component::Server::TCP is based on code, used with permission,
1450from Ann Barcomb E<lt>kudra@domaintje.comE<gt>.
1451
1452POE::Component::Server::TCP is based on code, used with permission,
1453from Jos Boumans E<lt>kane@cpan.orgE<gt>.
1454
1455=cut
1456
1457# rocco // vim: ts=2 sw=2 expandtab
1458# TODO - Edit.
1459