1package Perlbal::Plugin::Throttle;
2
3use strict;
4use warnings;
5
6our $VERSION = '1.20';
7
8use List::Util 'min';
9use Danga::Socket 1.59;
10use Perlbal 1.70;
11use Perlbal::ClientProxy ();
12use Perlbal::HTTPHeaders ();
13use Time::HiRes ();
14
15# Debugging flag
16use constant VERBOSE => $ENV{THROTTLE_VERBOSE} || 0;
17
18sub load {
19    # behavior
20    Perlbal::Service::add_tunable(
21        whitelist_file => {
22            check_role => '*',
23            des => "File containing CIDRs which are never throttled. (Net::CIDR::Lite must be installed.)",
24            check_type => 'file_or_none',
25        }
26    );
27    Perlbal::Service::add_tunable(
28        blacklist_file => {
29            check_role => '*',
30            des => "File containing CIDRs which are always denied outright. (Net::CIDR::Lite must be installed.)",
31            check_type => 'file_or_none',
32        }
33    );
34    Perlbal::Service::add_tunable(
35        default_action => {
36            check_role => '*',
37            des => "Whether to throttle or allow new connections from clients on neither the whitelist nor blacklist.",
38            check_type => [enum => [qw( allow throttle )]],
39            default => 'throttle',
40        }
41    );
42    Perlbal::Service::add_tunable(
43        blacklist_action => {
44            check_role => '*',
45            des => "Whether to deny or throttle connections from blacklisted IPs.",
46            check_type => [enum => [qw( deny throttle )]],
47            default => 'deny',
48        }
49    );
50
51    # filters
52    Perlbal::Service::add_tunable(
53        path_regex => {
54            check_role => '*',
55            des => "Regex which path portion of URI must match for throttling to be in effect.",
56        }
57    );
58    Perlbal::Service::add_tunable(
59        method_regex => {
60            check_role => '*',
61            des => "Regex which HTTP method must match for throttling to be in effect.",
62        }
63    );
64
65    # logging
66    Perlbal::Service::add_tunable(
67        log_events => {
68            check_role => '*',
69            des => q{Comma-separated list of events to log (ban, unban, whitelisted, blacklisted, concurrent, throttled, banned; all; none). If this is changed after the plugin is registered, the "throttle reload config" command must be issued.},
70            check_type => [regexp => qr/^(ban|unban|whitelisted|blacklisted|concurrent|throttled|banned|all|none| |,)+$/, "log_events is a comma-separated list of loggable events"],
71            default => 'all',
72        }
73    );
74    Perlbal::Service::add_tunable(
75        log_only => {
76            check_role => '*',
77            des => "Perform the full throttling calculation, but don't actually throttle or deny connections.",
78            check_type => 'bool',
79            default => 0,
80        }
81    );
82
83    # throttler parameters
84    Perlbal::Service::add_tunable(
85        throttle_threshold_seconds => {
86            check_role => '*',
87            des => "Minimum allowable time between requests. If a non-white/-blacklisted client makes another connection within this interval, it will be throttled for initial_delay seconds. Further connections will double the delay time.",
88            check_type => 'int',
89            default => 60,
90        }
91    );
92    Perlbal::Service::add_tunable(
93        initial_delay => {
94            check_role => '*',
95            des => "Minimum time for a connection to be throttled if occurring within throttle_threshold_seconds of last attempt.",
96            check_type => 'int',
97            default => 3,
98        }
99    );
100    Perlbal::Service::add_tunable(
101        max_delay => {
102            check_role => '*',
103            des => "Maximum time for a connection to be throttled after exponential increase from initial_delay.",
104            check_type => 'int',
105            default => 300,
106        }
107    );
108    Perlbal::Service::add_tunable(
109        max_concurrent => {
110            check_role => '*',
111            des => "Maximum number of connections accepted at a time from a single IP, per perlbal instance.",
112            check_type => 'int',
113            default => 2,
114        }
115    );
116    Perlbal::Service::add_tunable(
117        ban_threshold => {
118            check_role => '*',
119            des => "Number of accumulated violations required to temporarily ban the source IP.",
120            check_type => 'int',
121            default => 0,
122        }
123    );
124    Perlbal::Service::add_tunable(
125        ban_expiration => {
126            check_role => '*',
127            des => "Number of seconds after which banned IP is unbanned.",
128            check_type => 'int',
129            default => 60,
130        }
131    );
132
133    # memcached
134    Perlbal::Service::add_tunable(
135        memcached_servers => {
136            check_role => '*',
137            des => "List of memcached servers to share state in, if desired. (Cache::Memcached::Async must be installed.)",
138        }
139    );
140    Perlbal::Service::add_tunable(
141        memcached_async_clients => {
142            check_role => '*',
143            des => "Number of parallel Cache::Memcached::Async objects to use.",
144            check_type => 'int',
145            default => 10,
146        }
147    );
148    Perlbal::Service::add_tunable(
149        instance_name => {
150            check_role => '*',
151            des => "Name of throttler instance; instances with the same name will share knowledge of IPs.",
152            default => 'Throttle',
153        }
154    );
155
156    Perlbal::register_global_hook('manage_command.throttle', sub {
157        my $mc = shift->parse(qr/^
158                              throttle\s+
159                              (reload)\s+ # command
160                              (whitelist|blacklist|config)
161                              $/xi,
162                              "usage: throttle reload <config|whitelist|blacklist>");
163        my ($cmd, $what) = $mc->args;
164
165        my $svcname = $mc->{ctx}{last_created};
166        unless ($svcname) {
167            return $mc->err("No service name set. This command must be used after CREATE SERVICE <name> or USE <service_name>");
168        }
169
170        my $ss = Perlbal->service($svcname);
171        return $mc->err("Non-existent service '$svcname'") unless $ss;
172
173        my $cfg = $ss->{extra_config} ||= {};
174        my $stash = $cfg->{_throttle_stash} ||= {};
175
176        if ($cmd eq 'reload') {
177            if ($what eq 'whitelist') {
178                if (my $whitelist = $cfg->{whitelist_file}) {
179                    eval { $stash->{whitelist} = load_cidr_list($whitelist); };
180                    return $mc->err("Couldn't load $whitelist: $@")
181                        if $@ || !$stash->{whitelist};
182                }
183                else {
184                    return $mc->err("no whitelist file configured");
185                }
186            }
187            elsif ($what eq 'blacklist') {
188                if (my $blacklist = $cfg->{blacklist_file}) {
189                    eval { $stash->{blacklist} = load_cidr_list($blacklist); };
190                    return $mc->err("Couldn't load $blacklist: $@")
191                        if $@ || !$stash->{blacklist};
192                }
193                else {
194                    return $mc->err("no blacklist file configured");
195                }
196            }
197            elsif ($what eq 'config') {
198                $stash->{config_reloader}->();
199            }
200            else {
201                return $mc->err("unknown object to reload: $what");
202            }
203        }
204        else {
205            return $mc->err("unknown command $cmd");
206        }
207
208        return $mc->ok;
209    });
210}
211
212# magical Perlbal hook return value constants
213use constant HANDLE_REQUEST             => 0;
214use constant IGNORE_REQUEST             => 1;
215
216# indexes into logging flag list
217use constant LOG_BAN_ADDED              => 0;
218use constant LOG_BAN_REMOVED            => 1;
219use constant LOG_ALLOW_WHITELISTED      => 2;
220use constant LOG_ALLOW_DEFAULT          => 3;
221use constant LOG_DENY_BANNED            => 4;
222use constant LOG_DENY_BLACKLISTED       => 5;
223use constant LOG_DENY_CONCURRENT        => 6;
224use constant LOG_THROTTLE_BLACKLISTED   => 7;
225use constant LOG_THROTTLE_DEFAULT       => 8;
226use constant NUM_LOG_FLAGS              => 9;
227
228use constant RESULT_ALLOW               => 0;
229use constant RESULT_THROTTLE            => 1;
230use constant RESULT_DENY                => 2;
231
232# localized variable to track if a connection has already been throttled
233our $DELAYED = undef;
234
235sub register {
236    my ($class, $svc) = @_;
237
238    VERBOSE and Perlbal::log(info => "Registering Throttle plugin on service $svc->{name}");
239
240    my $cfg   = $svc->{extra_config}    ||= {};
241    my $stash = $cfg->{_throttle_stash} ||= {};
242
243    # these are allowed to die at register time
244    $stash->{whitelist} = load_cidr_list($cfg->{whitelist_file}) if $cfg->{whitelist_file};
245    $stash->{blacklist} = load_cidr_list($cfg->{blacklist_file}) if $cfg->{blacklist_file};
246
247    # several service tunables are cached in lexicals for efficiency. if these
248    # are changed, the "throttle reload config" command must be issued to
249    # update the cache. this implements the reloading (and initial loading).
250    my ($log, $path_regex, $method_regex);
251    my $loader = $stash->{config_reloader} = sub {
252        my @log_on_cfg = grep {length} split /[, ]+/, lc $cfg->{log_events};
253        my @log_events = (0) x NUM_LOG_FLAGS;
254        for (@log_on_cfg) {
255            $log_events[LOG_BAN_ADDED]              = 1 if $_ eq 'ban';
256            $log_events[LOG_BAN_REMOVED]            = 1 if $_ eq 'unban';
257            $log_events[LOG_ALLOW_WHITELISTED]      = 1 if $_ eq 'whitelisted';
258            $log_events[LOG_DENY_BANNED]            = 1 if $_ eq 'banned';
259            $log_events[LOG_DENY_BLACKLISTED]       =
260            $log_events[LOG_THROTTLE_BLACKLISTED]   = 1 if $_ eq 'blacklisted';
261            $log_events[LOG_DENY_CONCURRENT]        = 1 if $_ eq 'concurrent';
262            $log_events[LOG_THROTTLE_DEFAULT]       = 1 if $_ eq 'throttled';
263            @log_events = (1) x NUM_LOG_FLAGS           if $_ eq 'all';
264            @log_events = (0) x NUM_LOG_FLAGS           if $_ eq 'none';
265        }
266
267        $log = sub {};
268        if (grep {$_} @log_events) {
269            my $has_syslogger = eval { require Perlbal::Plugin::Syslogger; 1 };
270            if ($has_syslogger && $cfg->{syslog_host}) {
271                VERBOSE and Perlbal::log(info => "Using Perlbal::Plugin::Syslogger");
272                $log = sub {
273                    my $action = shift;
274                    return unless $log_events[$action];
275                    Perlbal::Plugin::Syslogger::send_syslog_msg($svc, @_);
276                };
277            }
278            else {
279                VERBOSE and Perlbal::log(warn => "Syslogger plugin unavailable, using Perlbal::log");
280                $log = sub {
281                    my $action = shift;
282                    return unless $log_events[$action];
283                    Perlbal::log(info => @_);
284                };
285            }
286        }
287
288        $path_regex   = $cfg->{path_regex}   ? qr/$cfg->{path_regex}/   : undef;
289        $method_regex = $cfg->{method_regex} ? qr/$cfg->{method_regex}/ : undef;
290    };
291    $loader->();
292
293    # structures for tracking IP states
294    my %throttled;
295    my %banned;
296    my $store = Perlbal::Plugin::Throttle::Store->new($cfg);
297
298    my $start_handler = sub {
299        my $retval = eval {
300            my $request_start = Time::HiRes::time;
301
302            VERBOSE and Perlbal::log(info => "In Throttle (%s)",
303                defined $DELAYED ? sprintf 'back after %.2fs', $DELAYED : 'initial'
304            );
305
306            my Perlbal::ClientProxy $cp = shift;
307            unless ($cp) {
308                VERBOSE and Perlbal::log(error => "Missing ClientProxy");
309                return HANDLE_REQUEST;
310            }
311
312            my $headers = $cp->{req_headers};
313            unless ($headers) {
314                VERBOSE and Perlbal::log(info => "Missing headers");
315                return HANDLE_REQUEST;
316            }
317            my $uri    = $headers->request_uri;
318            my $method = $headers->request_method;
319
320            my $ip = $cp->observed_ip_string() || $cp->peer_ip_string;
321            unless (defined $ip) {
322                # happens if client goes away
323                VERBOSE and Perlbal::log(warn => "Client went away");
324                $cp->send_response(500, "Internal server error.\n");
325                return IGNORE_REQUEST;
326            }
327
328            # back from throttling, all later checks were already passed
329            return HANDLE_REQUEST if defined $DELAYED;
330
331            # increment the count of throttled conns
332            $throttled{$ip}++;
333
334            my $result = sub {
335                # immediately passthrough whitelistees
336                if ($stash->{whitelist} && $stash->{whitelist}->find($ip)) {
337                    $log->(LOG_ALLOW_WHITELISTED, "Letting whitelisted ip $ip through");
338                    return RESULT_ALLOW;
339                }
340
341                # drop conns from banned IPs
342                if ($banned{$ip}) {
343                    $log->(LOG_DENY_BANNED, "Denying banned IP $ip");
344                    return RESULT_DENY;
345                }
346
347                # drop conns from banned/blacklisted IPs
348                if ($stash->{blacklist} && $stash->{blacklist}->find($ip)) {
349                    if ($cfg->{blacklist_action} eq 'deny') {
350                        $log->(LOG_DENY_BLACKLISTED, "Denying blacklisted IP $ip");
351                        return RESULT_DENY;
352                    }
353                    else {
354                        $log->(LOG_THROTTLE_BLACKLISTED, "Throttling blacklisted IP $ip");
355                        return RESULT_THROTTLE;
356                    }
357                }
358
359                if (exists $throttled{$ip} && $throttled{$ip} > $cfg->{max_concurrent}) {
360                    $log->(LOG_DENY_CONCURRENT, "Too many concurrent connections from $ip");
361                    return RESULT_DENY;
362                }
363
364                # only throttle matching requests
365                if (defined $path_regex && $uri !~ $path_regex) {
366                    VERBOSE && Perlbal::log(info => "This isn't a throttled URL: %s", $uri);
367                    return RESULT_ALLOW;
368                }
369                if (defined $method_regex && $method !~ $method_regex) {
370                    VERBOSE && Perlbal::log(info => "This isn't a throttled method: %s", $method);
371                    return RESULT_ALLOW;
372                }
373
374                return $cfg->{default_action} eq 'allow' ? RESULT_ALLOW : RESULT_THROTTLE;
375            }->();
376
377            if ($result == RESULT_DENY) {
378                unless ($cfg->{log_only}) {
379                    $cp->send_response(403, "Forbidden.\n");
380                    return IGNORE_REQUEST;
381                }
382            }
383            elsif ($result == RESULT_ALLOW) {
384                return HANDLE_REQUEST;
385            }
386
387            # now entering throttle path...
388
389            # check if we've seen this IP lately.
390            my $key = $cfg->{instance_name} . $ip;
391            $store->get(key => $key, timeout => $cfg->{initial_delay}, callback => sub {
392                my ($last_request_time, $violations) = @_;
393                $violations ||= 0;
394
395                # do an early set to update the last_request_time and
396                # expiration in case of early exit
397                $store->set(
398                    key     => $key,
399                    start   => $request_start,
400                    count   => $violations,
401                    exptime => $cfg->{throttle_threshold_seconds},
402                    timeout => $cfg->{initial_delay},
403                );
404
405                my $time_since_last_request;
406                if (defined $last_request_time) {
407                    $time_since_last_request = $request_start - $last_request_time;
408                }
409
410                VERBOSE and Perlbal::log(
411                    info => "%s; this request at %.3f; last at %s; interval is %s",
412                    $ip, $request_start,
413                    $last_request_time || 'n/a', $time_since_last_request || 'n/a'
414                );
415
416                my $handle_after = sub {
417                    my $delay = shift;
418                    $delay = 0 if $cfg->{log_only};
419
420                    # put request on the backburner
421                    $cp->watch_read(0);
422                    Danga::Socket->AddTimer($delay, sub {
423                        # we're now executing in a timer callback after
424                        # perlbal has been told to ignore the request. so if we
425                        # now want it handled it needs to be re-adopted.
426                        local $DELAYED = $delay; # to short-circuit throttling logic on the next pass through
427                        $cp->watch_read(1);
428                        $svc->adopt_base_client($cp);
429                    });
430
431                    return IGNORE_REQUEST;
432                };
433
434                # can we let it through immediately?
435                unless (defined $time_since_last_request) {
436                    # forgotten or haven't seen ip before
437                    $log->(LOG_ALLOW_DEFAULT, "Allowed unseen $ip");
438                    return $handle_after->(0);
439                }
440                if ($time_since_last_request >= $cfg->{throttle_threshold_seconds}) {
441                    # waited long enough
442                    $log->(LOG_ALLOW_DEFAULT, "Allowed reformed $ip");
443                    return $handle_after->(0);
444                }
445
446                # need to throttle, now figure out by how much. at least
447                # initial_delay, at most max_delay, exponentially increasing in
448                # between
449                my $delay = min($cfg->{initial_delay} * 2**$violations, $cfg->{max_delay});
450
451                $violations++;
452
453                # banhammer for great justice
454                if ($cfg->{ban_threshold} && $violations >= $cfg->{ban_threshold}) {
455                    $log->(LOG_BAN_ADDED, "Banning $ip for $cfg->{ban_expiration}s: %s", $uri);
456                    $banned{$ip}++ unless $cfg->{log_only};
457                    Danga::Socket->AddTimer($cfg->{ban_expiration}, sub {
458                        $log->(LOG_BAN_REMOVED, "Unbanning $ip");
459                        delete $banned{$ip};
460                    });
461                    $cp->close;
462                    return IGNORE_REQUEST;
463                }
464
465                $store->set(
466                    key     => $key,
467                    start   => $request_start,
468                    count   => $violations,
469                    exptime => $delay,
470                    timeout => $cfg->{initial_delay},
471                );
472
473                $log->(LOG_THROTTLE_DEFAULT, "Throttling $ip for $delay: %s", $uri);
474
475                # schedule request to be re-handled
476                return $handle_after->($delay);
477            });
478
479            # make sure we don't take up reading until readoption
480            $cp->watch_read(0);
481            return IGNORE_REQUEST;
482        };
483        if ($@) {
484            # if something horrible should happen internally, don't take out perlbal
485            Perlbal::log(err => "Throttle failed: '%s'", $@);
486            return HANDLE_REQUEST;
487        }
488        else {
489            return $retval;
490        }
491    };
492
493    my $end_handler = sub {
494        my Perlbal::ClientProxy $cp = shift;
495
496        my $ip = $cp->observed_ip_string() || $cp->peer_ip_string;
497        return unless $ip;
498
499        delete $throttled{$ip} unless --$throttled{$ip} > 0;
500    };
501
502    $svc->register_hook(Throttle => start_proxy_request => $start_handler);
503    $svc->register_hook(Throttle => end_proxy_request   => $end_handler);
504}
505
506sub load_cidr_list {
507    my $file = shift;
508
509    require Net::CIDR::Lite;
510
511    my $empty = 1;
512    my $list = Net::CIDR::Lite->new;
513
514    open my $fh, '<', $file or die "Unable to open file $file: $!";
515    while (my $line = <$fh>) {
516        $line =~ s/#.*//; # comments
517        if ($line =~ /([0-9\/\.]+)/) {
518            my $cidr = $1;
519            if (index($cidr, "/") < 0) {
520                # slash-less specifications are assumed to be singular IPs
521                $list->add_ip($cidr);
522            }
523            else {
524                $list->add($cidr);
525            }
526            $empty = 0;
527        }
528    }
529
530    die "$file contains no recognizable CIDRs\n" if $empty;
531
532    return $list;
533}
534
535package Perlbal::Plugin::Throttle::Store;
536
537sub new {
538    my $class = shift;
539    my $cfg = shift;
540
541    my $want_memcached = $cfg->{memcached_servers};
542    my $has_memcached = eval { require Cache::Memcached::Async; 1 };
543
544    if ($want_memcached && !$has_memcached) {
545        die "memcached support requested but Cache::Memcached::Async failed to load: $@\n";
546    }
547    return $want_memcached
548        ? Perlbal::Plugin::Throttle::Store::Memcached->new($cfg)
549        : Perlbal::Plugin::Throttle::Store::Memory->new($cfg);
550}
551
552package Perlbal::Plugin::Throttle::Store::Memcached;
553
554sub new {
555    my $class = shift;
556    my $cfg = shift;
557
558    my @servers = split /[,\s]+/, $cfg->{memcached_servers};
559    my @cxns = map {
560        Cache::Memcached::Async->new({ servers => \@servers })
561    } 1 .. $cfg->{memcached_async_clients};
562
563    return bless \@cxns, $class;
564}
565
566sub get {
567    my $self = shift;
568    my %p = @_;
569    $self->[rand @$self]->get(
570        $p{key},
571        timeout => $p{timeout},
572        callback => sub {
573            my $value = shift;
574            return $p{callback}->() unless $value;
575            return $p{callback}->(unpack('FS', $value));
576        },
577    );
578    return;
579}
580
581sub set {
582    my $self = shift;
583    my %p = @_;
584
585    $self->[rand @$self]->set(
586        $p{key} => pack('FS', $p{start}, $p{count}),
587        exptime => $p{exptime},
588        timeout => $p{timeout},
589    );
590}
591
592package Perlbal::Plugin::Throttle::Store::Memory;
593
594use Time::HiRes 'time';
595
596sub new {
597    my $class = shift;
598    my $cfg = shift;
599    return bless {}, $class;
600}
601
602sub get {
603    my $self = shift;
604    my %p = @_;
605    my $entry = $self->{$p{key}};
606
607    return $p{callback}->($entry->[1], $entry->[2]) if $entry && time < $entry->[0];
608    return $p{callback}->();
609}
610
611sub set {
612    my $self = shift;
613    my %p = @_;
614    $self->{$p{key}} = [time + $p{exptime}, $p{start}, $p{count}];
615    return;
616}
617
6181;
619
620__END__
621
622=head1 NAME
623
624Perlbal::Plugin::Throttle - Perlbal plugin that throttles connections from
625hosts that connect too frequently.
626
627=head1 SYNOPSIS
628
629    # in perlbal.conf
630
631    LOAD Throttle
632
633    CREATE POOL web
634        POOL web ADD 10.0.0.1:80
635
636    CREATE SERVICE throttler
637        SET role                        = reverse_proxy
638        SET listen                      = 0.0.0.0:80
639        SET pool                        = web
640
641        # adjust throttler aggressiveness
642        SET initial_delay               = 10
643        SET max_delay                   = 60
644        SET throttle_threshold_seconds  = 3
645        SET max_concurrent              = 2
646        SET ban_threshold               = 4
647        SET ban_expiration              = 180
648
649        # limit which requests are throttled
650        SET path_regex                  = ^/webapp/
651        SET method_regex                = ^GET$
652
653        # allow or ban specific addresses or range (requires Net::CIDR::Lite)
654        SET whitelist_file              = conf/whitelist.txt
655        SET blacklist_file              = conf/blacklist.txt
656
657        # granular logging (requires Perlbal::Plugin::Syslogger)
658        SET log_events                  = ban,unban,throttled,banned
659        SET log_only                    = false
660
661        # share state between perlbals (requires Cache::Memcached::Async)
662        SET memcached_servers           = 10.0.2.1:11211,10.0.2.2:11211
663        SET memcached_async_clients     = 4
664        SET instance_name               = mywebapp
665
666        SET plugins                     = Throttle
667    ENABLE throttler
668
669=head1 DESCRIPTION
670
671This plugin intercepts HTTP requests to a Perlbal service and slows or drops
672connections from IP addresses which are determined to be connecting too fast.
673
674=head1 BEHAVIOR
675
676An IP address address may be in one of four states depending on its recent
677activity; that state determines how new requests from the IP are handled:
678
679=over 4
680
681=item * B<allowed>
682
683An IP begins in the B<allowed> state. When a request is received from an IP in
684this state, the request is handled immediately and the IP enters the
685B<probation> state.
686
687=item * B<probation>
688
689If no requests are received from an IP in the B<probation> state for
690I<throttle_threshold_seconds>, it returns to the B<allowed> state.
691
692When a new request is received from an IP in the B<probation> state, the IP
693enters the B<throttled> state and is assigned a I<delay> property initially
694equal to I<initial_delay>. Connection to a backend is postponed for I<delay>
695seconds while perlbal continues to work. If the connection is still open after
696the delay, the request is then handled normally. A dropped connection does not
697change the IP's I<delay> value.
698
699=item * B<throttled>
700
701If no requests are received from an IP in the B<throttled> state for
702I<delay> seconds, it returns to the B<probation> state.
703
704When a new request is received from an IP in the B<throttled> state, its
705I<violations> property is incremented, and its I<delay> property is
706doubled (up to a maximum of I<max_delay>). The request is postponed for the new
707value of I<delay>.
708
709Only after the most recently created connection from a given IP exits the
710B<throttled> state do I<violations> and I<delay> reset to 0.
711
712Furthermore, if the I<violations> exceeds I<ban_threshold>, the connection
713is closed and the IP moves to the B<banned> state.
714
715IPs in the B<throttled> state may have no more than I<max_concurrent>
716connections being delayed at once. Any additional requests received in that
717circumstance are sent a "503 Too many connections" response. Long-running
718requests which have already been connected to a backend do not count towards
719this limit.
720
721=item * B<banned>
722
723New connections from IPs in the banned state are immediately closed with a 403
724error response.
725
726An IP leaves the B<banned> state after I<ban_expiration> seconds have
727elapsed.
728
729=back
730
731=head1 FEATURES
732
733=over 4
734
735=item * IP whitelist
736
737Connections from IPs/CIDRs listed in the file specified by I<whitelist_file>
738are always allowed.
739
740=item * IP blacklist
741
742Connections from IPs/CIDRs listed in the file specified by I<blacklist_file>
743immediately sent a "403 Forbidden" response.
744
745=item * Flexible attack response
746
747For services where throttling should not normally be enabled, use the
748I<default_action> tunable. When I<default_action> is set to "allow", new
749connections from non-white/blacklisted IPs will not be throttled.
750
751Furthermore, if throttling should only apply to specific clients, set
752I<blacklist_action> to "throttle". Blacklisted connections will then be
753throttled instead of denied.
754
755=item * Dynamic configuration
756
757Most service tunables may be updated from the management port, after which the
758new values will be respected (although see L</CAVEATS>). To reload the
759whitelist and blacklist files, issue the I<throttle reload whitelist> or
760I<throttle reload blacklist> command to the service.
761
762=item * Path specificity
763
764Throttling may be restricted to URI paths matching the I<path_regex> regex.
765
766=item * External shared state
767
768The plugin stores state which IPs have been seen in a memcached(1) instance.
769This allows many throttlers to share their state and also minimizes memory use
770within the perlbal. If state exceeds the capacity of the memcacheds, the
771least-recently seen IPs will be forgotten, effectively resetting them to the
772B<allowed> state.
773
774Orthogonally, multiple throttlers which need to share memcacheds but not state
775may specify distinct I<instance_name> values.
776
777=item * Logging
778
779If Perlbal::Plugin::Syslogger is installed and registered with the service,
780Throttle can use it to send syslog messages regarding actions that are taken.
781Granular control for which events are logged is available via the I<log_events>
782parameter. I<log_events> is composed of one or more of the following events,
783separated by commas:
784
785=over 4
786
787=item * ban
788
789Log when a temporary local ban is added for an IP address.
790
791=item * unban
792
793Log when a temporary local ban is removed for an IP address.
794
795=item * whitelisted
796
797Log when a request is allowed because the source IP is on the whitelist.
798
799=item * blacklisted
800
801Log when a request is denied or throttled because the source IP is on the
802blacklist.
803
804=item * banned
805
806Log when a request is denied because the source IP is on the temporary ban list
807for connecting excessively.
808
809=item * concurrent
810
811Log when a request is denied because the source IP has too many open connections
812waiting to be unthrottled.
813
814=item * throttled
815
816Log when a request is throttled because the source IP was not on the whitelist
817or blacklist.
818
819=item * all
820
821Enables all the above logging options.
822
823=item * none
824
825Disables all the above logging options.
826
827=back
828
829=back
830
831=head1 CAVEATS
832
833=over 4
834
835=item * Dynamic configuration changes
836
837Changes to certain service tunables will not be noticed until the B<throttle
838reload config> management command is issued. These include I<log_events>,
839I<path_regex>, and I<method_regex>).
840
841Changes to certain other tunables will not be respected after the plugin has
842been registered. These include I<memcached_servers> and
843I<memcached_async_clients>.
844
845=item * List loading is blocking
846
847The I<throttle reload whitelist> and I<throttle reload blacklist> management
848commands load the whitelist and blacklist files synchronously, which will cause
849the perlbal to hang until it completes.
850
851=item * Redirects
852
853If a handled request returns a 30x response code and the redirect URI is also
854throttled, then the client's attempt to follow the redirect will necessarily be
855delayed by I<initial_delay>. Fixing this would require that the plugin inspect
856the HTTP response headers, which would incur a lot of overhead. To workaround,
857try to have your backend not return 30x's if both the original and redirect URI
858are proxied by the same throttler instance (yes, this is difficult for the case
859where a backend 302s to add a trailing / to a directory).
860
861=back
862
863=head1 OPTIONAL DEPENDENCIES
864
865=over 4
866
867=item * Cache::Memcached::Async
868
869Required for memcached support. This is the supported way to share state
870between different perlbal instances.
871
872=item * Net::CIDR::Lite
873
874Required for blacklist/whitelist support.
875
876=item * Perlbal::Plugin::Syslogger
877
878Required for event logging support.
879
880=back
881
882=head1 SEE ALSO
883
884=over 4
885
886=item * List of tunables in Throttle.pm.
887
888=back
889
890=head1 TODO
891
892=over 4
893
894=item * Fix white/blacklist loading
895
896Load CIDR lists asynchronously (perhaps in the manner of
897Perlbal::Pool::_load_nodefile_async).
898
899=back
900
901=head1 AUTHOR
902
903Adam Thomason, E<lt>athomason@cpan.orgE<gt>
904
905=head1 COPYRIGHT AND LICENSE
906
907Copyright (C) 2007-2011 by Say Media Inc, E<lt>cpan@sixapart.comE<gt>
908
909This library is free software; you can redistribute it and/or modify it under
910the same terms as Perl itself, either Perl version 5.8.6 or, at your option,
911any later version of Perl 5 you may have available.
912
913=cut
914