swish/commit

New upstream files

authorJan Wielemaker
Tue May 23 11:57:48 2017 +0200
committerJan Wielemaker
Tue May 23 12:00:43 2017 +0200
commit1f7e4e38054b3386743737af73b94dfd2bf3b09a
tree426e844a3465825879c2e0d94018b9f3808dd158
parent435af67ee749efe7a0474d770a08b763d63a975f
Diff style: patch stat
diff --git a/examples/stats.swinb b/examples/stats.swinb
index 6af0e4e..cf35ce3 100644
--- a/examples/stats.swinb
+++ b/examples/stats.swinb
@@ -109,6 +109,16 @@ The number of Pegines denotes the number of actively executing queries.  These q
 chart(hour, [pengines,d_cpu], Chart).
 </div>
 
+<div class="nb-cell markdown">
+### Number of threads and visitors
+
+Threads are used as HTTP workers, pengines and some adminstrative tasks.  Visitors is the number of open websockets, which reflects the number of browser windows watching this page.
+</div>
+
+<div class="nb-cell query">
+chart(hour, [pengines,threads,visitors], Chart).
+</div>
+
 <div class="nb-cell markdown">
 ### Memory usage over the past hour
 
@@ -124,6 +134,8 @@ chart(hour, [rss_mb,heap_mb,stack_mb,free_mb], Chart).
 ## Health statistics
 
 The statistics below assesses the number of *Pengines* (actively executing queries from users) and the *highlight states*, the number of server-side mirrors we have from client's source code used to compute the semantically enriched tokens.   If such states are not explicitly invalidated by the client, they are removed after having not been accessed for one hour.  The *stale modules* count refers to temporary modules that are not associated to a Pengine, nor to a highlight state and probably indicate a leak.
+
+The two queries below extract information about stale modules and threads that have died.  These are used to help debugging related leaks.
 </div>
 
 <div class="nb-cell program" data-singleline="true">
@@ -140,4 +152,12 @@ stats([stale_modules-Stale|Pairs]) :-
 stats(Stats).
 </div>
 
+<div class="nb-cell query" data-chunk="10" data-tabled="true" name="q2">
+pengine_stale_module(Module, State).
+</div>
+
+<div class="nb-cell query" data-chunk="10" data-tabled="true" name="q1">
+swish_died_thread(Thread, State).
+</div>
+
 </div>
diff --git a/lib/swish/authenticate.pl b/lib/swish/authenticate.pl
new file mode 100644
index 0000000..4c6ef2e
--- /dev/null
+++ b/lib/swish/authenticate.pl
@@ -0,0 +1,164 @@
+/*  Part of SWISH
+
+    Author:        Jan Wielemaker
+    E-mail:        J.Wielemaker@cs.vu.nl
+    WWW:           http://www.swi-prolog.org
+    Copyright (C): 2017, VU University Amsterdam
+			 CWI Amsterdam
+    All rights reserved.
+
+    Redistribution and use in source and binary forms, with or without
+    modification, are permitted provided that the following conditions
+    are met:
+
+    1. Redistributions of source code must retain the above copyright
+       notice, this list of conditions and the following disclaimer.
+
+    2. Redistributions in binary form must reproduce the above copyright
+       notice, this list of conditions and the following disclaimer in
+       the documentation and/or other materials provided with the
+       distribution.
+
+    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
+    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
+    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
+    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
+    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
+    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
+    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
+    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
+    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
+    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
+    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
+    POSSIBILITY OF SUCH DAMAGE.
+*/
+
+:- module(swish_authenticate,
+          [ authenticate/2,                     % +Request, -Authentity
+            user_property/2                     % +Authentity, ?Property
+          ]).
+:- use_module(library(http/http_wrapper)).
+:- use_module(library(debug)).
+:- use_module(library(broadcast)).
+
+:- use_module(config).
+
+/** <module> Authentication access for SWISH
+
+This module (depending on the loaded  configuration) identifies the user
+based on the HTTP request.
+
+@see pep.pl for _authorization_ issues.
+*/
+
+%!  authenticate(+Request, -Identity:dict) is det.
+%
+%   Establish the identity behind  the  HTTP   Request.  There  are  two
+%   scenarios.
+%
+%     - The entire server is protected using HTTP authentication.  In
+%       this case this predicate may throw an HTTP challenge or a
+%       forbidden exception.
+%     - The server allows for mixed anonymous and logged in usage. Login
+%       may use HTTP or federated login (oauth2).
+%
+%   @throws http_reply(_) HTTP authentication and permission exceptions
+%   if config-available/auth_http_always.pl is enabled.
+
+authenticate(Request, Auth) :-
+    http_peer(Request, Peer),
+    http_auth(Request, Auth0),
+    profile_auth(Request, Auth1),
+    Auth2 = Auth0.put(Auth1).put(peer, Peer),
+    identity(Auth2, Auth),
+    debug(authenticate, 'Identity: ~p', [Auth]).
+
+:- multifile
+    swish_config:authenticate/2,
+    swish_config:user_profile/2.
+
+http_auth(Request, Auth) :-
+    (   swish_config:authenticate(Request, User)   % throws http_reply(_)
+    ->  true
+    ;   swish_config:user_info(Request, local, UserInfo),
+        User = UserInfo.get(user)
+    ),
+    !,
+    Auth = auth{user:User, identity_provider:local, external_identity:User}.
+http_auth(_Request, auth{}).
+
+profile_auth(Request, Auth) :-
+    swish_config:user_profile(Request, Profile),
+    Auth = _{identity_provider: _,
+             external_identity: _,
+             profile_id:_},
+    Auth :< Profile,
+    !.
+profile_auth(_, auth{}).
+
+identity(Auth0, Auth) :-
+    _{identity_provider:Provider, external_identity:ExtID} :< Auth0,
+    !,
+    atomic_list_concat([Provider,ExtID], :, Identity),
+    Auth = Auth0.put(identity, Identity).
+identity(Auth, Auth).
+
+
+%!  user_property(+Identity, ?Property) is nondet.
+%
+%   True when Identity has Property. Defined properties are:
+%
+%     - peer(Atom)
+%     Remote IP address
+%     - identity(Atom)
+%     Identity as provided by some identity provider
+%     - identity_provider(Atom)
+%     Subsystem that identified the user
+%     - external_identity(Atom)
+%     Identity as provided by the identity_provider
+%     - profile_id(Atom)
+%     Identifier of the profile we have on this user.
+%     - login(Atom)
+%     Same as identity_provider(Atom)
+%     - name(Atom)
+%     Name associated with the identity
+%     - email(Atom)
+%     Email associated with the identity
+
+user_property(Identity, Property) :-
+    current_user_property(Property, How),
+    user_property_impl(Property, How, Identity).
+
+user_property_impl(Property, dict, Identity) :- !,
+    Property =.. [Name,Value],
+    Value = Identity.get(Name).
+user_property_impl(Property, broadcast, Identity) :-
+    broadcast_request(identity_property(Identity, Property)).
+user_property_impl(login(By), _, Identity) :-
+    By = Identity.get(identity_provider).
+
+
+current_user_property(peer(_Atom),                dict).
+current_user_property(identity(_Atom),            dict).
+current_user_property(external_identity(_String), dict).
+current_user_property(identity_provider(_Atom),   dict).
+current_user_property(profile_id(_Atom),          dict).
+
+current_user_property(login(_IdProvider),         derived).
+current_user_property(name(_Name),                broadcast).
+current_user_property(email(_Email),              broadcast).
+
+
+		 /*******************************
+		 *        PENGINE HOOKS		*
+		 *******************************/
+
+%!  pengines:authentication_hook(+Request, +Application, -User)
+%
+%   Is called from the /pengine/create request   to establish the logged
+%   in user.
+
+:- multifile pengines:authentication_hook/3.
+
+pengines:authentication_hook(Request, _Application, User) :-
+    authenticate(Request, User).
diff --git a/lib/swish/avatar.pl b/lib/swish/avatar.pl
new file mode 100644
index 0000000..cacfba7
--- /dev/null
+++ b/lib/swish/avatar.pl
@@ -0,0 +1,164 @@
+/*  Part of SWISH
+
+    Author:        Jan Wielemaker
+    E-mail:        J.Wielemaker@cs.vu.nl
+    WWW:           http://www.swi-prolog.org
+    Copyright (C): 2014-2016, VU University Amsterdam
+			      CWI Amsterdam
+    All rights reserved.
+
+    Redistribution and use in source and binary forms, with or without
+    modification, are permitted provided that the following conditions
+    are met:
+
+    1. Redistributions of source code must retain the above copyright
+       notice, this list of conditions and the following disclaimer.
+
+    2. Redistributions in binary form must reproduce the above copyright
+       notice, this list of conditions and the following disclaimer in
+       the documentation and/or other materials provided with the
+       distribution.
+
+    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
+    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
+    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
+    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
+    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
+    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
+    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
+    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
+    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
+    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
+    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
+    POSSIBILITY OF SUCH DAMAGE.
+*/
+
+:- module(avatar,
+	  [ email_gravatar/2,			% +Email, -AvatarURL
+	    valid_gravatar/1,			% +AvatarURL
+	    random_avatar/1,			% -AvatarURL
+	    release_avatar/1,			% +AvatarURL
+
+	    clean_avatar_cache/0
+	  ]).
+:- use_module(library(uri)).
+:- use_module(library(md5)).
+:- use_module(library(lists)).
+:- use_module(library(random)).
+:- use_module(library(apply)).
+:- use_module(library(http/http_path)).
+:- use_module(library(http/http_open)).
+:- use_module(library(error)).
+
+/** <module> Avatar management
+
+This module provides access to avatar handling.
+*/
+
+%%	email_avatar(+Email, -AvatarImageLink) is det.
+%
+%	@see https://en.gravatar.com/site/implement/hash/
+%	@see https://en.gravatar.com/site/implement/images/
+
+email_gravatar(Email, AvatarURL) :-
+	downcase_atom(Email, CanonicalEmail),
+	md5_hash(CanonicalEmail, Hash, []),
+	atom_concat('/avatar/', Hash, Path),
+	uri_data(scheme,    Components, http),
+	uri_data(authority, Components, 'www.gravatar.com'),
+	uri_data(path,      Components, Path),
+	uri_components(AvatarURL, Components).
+
+
+%%	valid_gravatar(+URL) is semidet.
+%
+%	True if URL is a real gavatar.
+
+valid_gravatar(URL) :-
+	string_concat(URL, "?d=404", URL2),
+	catch(http_open(URL2, In, [method(head)]),
+	      error(existence_error(_,_),_),
+	      fail),
+	close(In).
+
+
+%%	random_avatar(-AvatarURL) is det.
+%
+%	Generate a random avatar image url. This uses an arbitrary image
+%	from  the  virtual  path  icons(avatar).  This  predicate  never
+%	replies with the same URL.
+%
+%	@arg AvatarURL is a relative URL (does not include the host)
+%	@error resource_error(avatars) if no more avatars are available
+
+random_avatar(AvatarURL) :-
+	avatar_cache(_Size),
+	repeat,
+	findall(I, free_avatar(I), L),
+	    (	L == []
+	    ->	resource_error(avatars)
+	    ;	random_member(A, L),
+		avatar(A, AvatarURL),
+		with_mutex(avatar, claim_avatar(A)),
+		!
+	    ).
+
+free_avatar(I) :-
+	avatar(I, _),
+	\+ used_avatar(I).
+
+claim_avatar(I) :-
+	used_avatar(I), !, fail.
+claim_avatar(I) :-
+	assertz(used_avatar(I)).
+
+%!	release_avatar(+URL) is det.
+%
+%	Release the avatar to the pool of free avatars.
+
+release_avatar(URL0) :-
+	atom_string(URL, URL0),
+	forall(avatar(I, URL),
+	       retractall(used_avatar(I))).
+
+clean_avatar_cache :-
+	retractall(avatar_cache_size(_)),
+	retractall(avatar(_,_)).
+
+:- dynamic
+	used_avatar/1,
+	avatar_cache_size/1,
+	avatar/2.
+:- volatile
+	used_avatar/1,
+	avatar_cache_size/1,
+	avatar/2.
+
+avatar_cache(Size) :-
+	avatar_cache_size(Size), !.
+avatar_cache(Size) :-
+	findall(Path, avatar_path(Path), Paths),
+	foldl(assert_avatar, Paths, 0, Size0),
+	assertz(avatar_cache_size(Size0)),
+	Size = Size0.
+
+avatar_path(icons(avatar/File)) :-
+	absolute_file_name(icons(avatar), Dir,
+			   [ file_type(directory),
+			     solutions(all)
+			   ]),
+	directory_files(Dir, Files),
+	member(File, Files),
+	file_name_extension(_, Ext, File),
+	downcase_atom(Ext, LwrExt),
+	image_extension(LwrExt).
+
+image_extension(png).
+image_extension(jpg).
+image_extension(jpeg).
+image_extension(gif).
+
+assert_avatar(Path, N, N2) :-
+	http_absolute_location(Path, HREF, []),
+	assertz(avatar(N, HREF)),
+	N2 is N+1.
diff --git a/lib/swish/bootstrap.pl b/lib/swish/bootstrap.pl
new file mode 100644
index 0000000..047ec0b
--- /dev/null
+++ b/lib/swish/bootstrap.pl
@@ -0,0 +1,440 @@
+/*  Part of SWISH
+
+    Author:        Jan Wielemaker
+    E-mail:        J.Wielemaker@cs.vu.nl
+    WWW:           http://www.swi-prolog.org
+    Copyright (C): 2017, VU University Amsterdam
+			 CWI Amsterdam
+    All rights reserved.
+
+    Redistribution and use in source and binary forms, with or without
+    modification, are permitted provided that the following conditions
+    are met:
+
+    1. Redistributions of source code must retain the above copyright
+       notice, this list of conditions and the following disclaimer.
+
+    2. Redistributions in binary form must reproduce the above copyright
+       notice, this list of conditions and the following disclaimer in
+       the documentation and/or other materials provided with the
+       distribution.
+
+    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
+    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
+    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
+    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
+    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
+    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
+    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
+    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
+    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
+    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
+    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
+    POSSIBILITY OF SUCH DAMAGE.
+*/
+
+:- module(swish_bootstrap,
+          [ bt_form//2,                 % +Fields, +Options
+            bt_button//4,               % +Name, +Type, +IOptions, +Options
+
+            name_label/2                % +Name, -Label
+          ]).
+:- use_module(library(option)).
+:- use_module(library(occurs)).
+:- use_module(library(error)).
+:- use_module(library(http/html_write)).
+
+/** <module> Bootstrap form generator
+
+This library provides HTML rules for constructing Bootstrap forms.
+*/
+
+%!  bt_form(+Contents, +Options)//
+%
+%   Emit a Bootstrap form from Contents.  Each element of Contents is
+%   one of the following terms:
+%
+%     - input(Name, Type, InputOptions)
+%     - select(Name, Values, SelectOptions)
+%     - checkboxes(Name, Values, BoxOptions)
+%     - button(Name, Type, ButtonOptions)
+%     - button_group(Buttons, GroupOptions)
+%     - hidden(Name, Value)
+%
+%   Options processed:
+%
+%     - class(+Class)
+%     One of 'form-inline' or 'form-horizontal'.  Default is a vertical
+%     form.
+%     - label_columns(+SizeCount)
+%     Number of columns of the grid to use for the label.  In use for
+%     'form-horizontal'.  Default is sm-2 (a pair)
+
+bt_form(Fields, Options) -->
+    { form_attributes(Atts, Options) },
+    html(form(Atts, \bt_form_content(Fields, Options))).
+
+form_attributes([class(Class)], Options) :-
+    option(class(Class), Options).
+form_attributes([], _).
+
+bt_form_content([], _) --> [].
+bt_form_content([H|T], Options) -->
+    bt_form_element(H, Options),
+    bt_form_content(T, Options).
+
+
+%!  form_style(+Style, +Options)
+
+form_style(horizontal, Options) :-
+    option(class(Class), Options),
+    sub_term('form-horizontal', Class).
+form_style(inline, Options) :-
+    option(class(Class), Options),
+    sub_term('form-inline', Class).
+form_style(vertical, Options) :-
+    (   option(class(Class), Options)
+    ->  \+ sub_term('form-inline', Class),
+        \+ sub_term('form-horizontal', Class)
+    ;   true
+    ).
+
+
+%!  bt_form_element(+Term, +Options)//
+%
+%   Add a single element to the form.
+
+bt_form_element(input(Name, Type, IOptions), Options) -->
+    html(div(class('form-group'),
+             [ \bt_label(Name, IOptions, Options),
+               \bt_input(Name, Type, IOptions, Options)
+             ])).
+bt_form_element(select(Name, Values, IOptions), Options) -->
+    html(div(class('form-group'),
+             [ \bt_label(Name, IOptions, Options),
+               \bt_select(Name, Values, IOptions, Options)
+             ])).
+bt_form_element(checkboxes(Name, Values, IOptions), Options) -->
+    html(div(class('form-group'),
+             [ \bt_label(Name, IOptions, Options),
+               \bt_checkboxes(Name, Values, IOptions, Options)
+             ])).
+bt_form_element(textarea(Name, IOptions), Options) -->
+    html(div(class('form-group'),
+             [ \bt_label(Name, IOptions, Options),
+               \bt_textarea(Name, IOptions, Options)
+             ])).
+bt_form_element(button(Name, Type, IOptions), Options) -->
+    bt_button(Name, Type, IOptions, Options).
+bt_form_element(button_group(Buttons, IOptions), Options) -->
+    bt_button_group(Buttons, IOptions, Options).
+bt_form_element(hidden(Name, Value), _Options) -->
+    html(input([type(hidden),name(Name),value(Value)])).
+
+%!  bt_label(+Name, +ElementOptions, +FormsOptions)//
+%
+%   Emit a label.
+
+bt_label(Name, IOptions, Options) -->
+    { phrase(label_attr(Options), Attrs) },
+    html(label([for(Name)|Attrs], \label(Name, IOptions))).
+
+label_attr(Options) -->
+    { form_style(horizontal, Options),
+      option(label_columns(Size-Count), Options, sm-2),
+      atomic_list_concat([col,Size,Count], -, Class)
+    },
+    [ class(['control-label', Class]) ].
+label_attr(_) --> [].
+
+
+
+%!  bt_input(+Name, +Type, +InputOptions, +FormOptions)//
+%
+%   Emit an input element.  InputOptions are:
+%
+%     - value(+Value)
+%     Initial value of the input
+%     - disabled(+Boolean)
+%     If `true`, the input is inactive.
+%     - readonly(+Boolean)
+%     If `true`, the input cannot be edited.
+
+:- html_meta(horizontal_input(html, +, +, +, ?, ?)).
+
+bt_input(Name, Type, InputOptions, FormOptions) -->
+    horizontal_input(\bt_input_elem(Name, Type, InputOptions, FormOptions),
+                     [], [], FormOptions),
+    !.
+bt_input(Name, Type, InputOptions, FormOptions) -->
+    bt_input_elem(Name, Type, InputOptions, FormOptions).
+
+horizontal_input(HTML, Classes, Attrs, FormOptions) -->
+    { form_style(horizontal, FormOptions),
+      option(label_columns(Size-Count), FormOptions, sm-2),
+      FieldCols is 12-Count,
+      atomic_list_concat([col,Size,FieldCols], -, Class)
+    },
+    html(div([class([Class|Classes])|Attrs], HTML)).
+
+bt_input_elem(Name, checkbox, InputOptions, _FormOptions) -->
+    !,
+    { phrase(checkbox_attr(InputOptions), Attrs) },
+    html(input([type(checkbox), name(Name)|Attrs])).
+bt_input_elem(Name, Type, InputOptions, _FormOptions) -->
+    { phrase(input_attr(InputOptions), Attrs),
+      phrase(classes(InputOptions), Classes),
+      list_to_set(['form-control'|Classes], InputClasses)
+    },
+    html(input([type(Type), class(InputClasses), name(Name)|Attrs])).
+
+checkbox_attr(Options) -->
+    ( checkbox_value(Options) -> [] ; [] ),
+    ( input_disabled(Options) -> [] ; [] ),
+    ( input_readonly(Options) -> [] ; [] ),
+    data(Options).
+
+checkbox_value(Options) -->
+    { option(value(true), Options) },
+    [ checked(checked) ].
+
+input_attr(Options) -->
+    ( input_value(Options) -> [] ; [] ),
+    ( input_disabled(Options) -> [] ; [] ),
+    data(Options).
+
+input_value(Options) -->
+    { option(value(Value), Options) },
+    [ value(Value) ].
+input_disabled(Options) -->
+    { option(disabled(true), Options) },
+    [ disabled(disabled) ].
+input_readonly(Options) -->
+    { option(readonly(true), Options) },
+    [ readonly(readonly) ].
+
+%!  bt_select(+Name, +Values, +SelectOptions, +FormOptions)//
+%
+%   Emit a <select> element.  SelectOptions:
+%
+%     - value(Value)
+%       If present, provides the preselected value
+%     - size(Size)
+%       Provides the number of visible options.
+
+bt_select(Name, Values, SelectOptions, FormOptions) -->
+    horizontal_input(\bt_select_elem(Name, Values, SelectOptions, FormOptions),
+                     [], [], FormOptions).
+
+bt_select_elem(Name, Values, SelectOptions, _FormOptions) -->
+    { option(value(Value), SelectOptions, _),
+      phrase(( (select_size(SelectOptions)     -> [] ; []),
+               (select_multiple(SelectOptions) -> [] ; [])
+             ), Opts)
+    },
+    html(select([name(Name),class('form-control')|Opts],
+                \select_options(Values, Value, SelectOptions))).
+
+select_size(Options) -->
+    { option(size(Size), Options) },
+    [ size(Size) ].
+select_multiple(Options) -->
+    { option(multiple(true), Options) },
+    [ multiple(multiple) ].
+
+select_options([], _, _) -->
+    [].
+select_options([H|T], Value, Options) -->
+    select_option_1(H, Value, Options),
+    select_options(T, Value, Options).
+
+select_option_1(Value, Selected, _Options) -->
+    { (atom(Value) ; string(Value)),
+      !,
+      name_label(Value, Label),
+      (   Value == Selected
+      ->  Opts = [selected(selected)]
+      ;   Opts = []
+      )
+    },
+    html(option([value(Value)|Opts], Label)).
+select_option_1(Value, _, _) -->
+    { domain_error(bt_select_option, Value) }.
+
+%!  bt_checkboxes(+Name, +Values, +SelectOptions, +FormOptions)//
+%
+%   Set of checkboxes reported as an array that is a subset of Values.
+
+bt_checkboxes(Name, Values, CBOptions, FormOptions) -->
+    horizontal_input(\checkboxes(Values, CBOptions),
+                     [checkboxes, array], name(Name), FormOptions).
+
+checkboxes([], _) -->
+    [].
+checkboxes([H|T], Options) -->
+    checkbox(H, Options),
+    checkboxes(T, Options).
+
+checkbox(Value, Options) -->
+    { name_label(Value, Label),
+      (   option(value(Selected), Options),
+          memberchk(Value, Selected)
+      ->  Opts = [checked(checked)]
+      ;   Opts = []
+      )
+    },
+    html(label(class('checkbox-inline'),
+               [ input([ type(checkbox), name(Value), autocomplete(false)
+                       | Opts
+                       ]),
+                 Label
+               ])).
+
+%!  bt_textarea(+Name, +TextAreaOptions, +FormOptions)//
+
+bt_textarea(Name, TextAreaOptions, FormOptions) -->
+    horizontal_input(\bt_textarea_elem(Name, TextAreaOptions, FormOptions),
+                     [], [], FormOptions),
+    !.
+bt_textarea(Name, TextAreaOptions, FormOptions) -->
+    bt_textarea_elem(Name, TextAreaOptions, FormOptions).
+
+
+bt_textarea_elem(Name, TextAreaOptions, _FormOptions) -->
+    { option(rows(Rows), TextAreaOptions, 4)
+    },
+    html(textarea([ class('form-control)'),
+                    rows(Rows),
+                    name(Name),
+                    style('width:100%')
+                  ], [])).
+
+
+%!  bt_button_group(+Buttons, +ButtonOptions, +FormOptions)//
+%
+%   Emit a div for a group of buttons.
+
+bt_button_group(Buttons, _ButtonOptions, FormOptions) -->
+    { form_style(horizontal, FormOptions),
+      !,
+      option(label_columns(_-Count), FormOptions, sm-2),
+      Count12 is 12-Count,
+      atomic_list_concat([col,xs,offset,Count], -, Offset),
+      atomic_list_concat([col,xs,Count12], -, Width)
+    },
+    html(div(class('form-group'),
+             div(class([Offset,Width]),
+                 \bt_form_content(Buttons, FormOptions)))).
+bt_button_group(Buttons, _ButtonOptions, FormOptions) -->
+    html(div(class(['col-xs-12', 'text-center']),
+             \bt_form_content(Buttons, FormOptions))).
+
+
+%!  bt_button(+Name, +Type, +ButtonOptions, +FormOptions)//
+
+bt_button(Name, Type, IOptions, Options) -->
+    { phrase(button_classes(IOptions, Options), BtnClasses),
+      phrase(data(IOptions), DataAttrs)
+    },
+    html(button([ type(Type),
+                  name(Name),
+                  class([btn|BtnClasses])
+                | DataAttrs
+                ],
+                \label(Name, IOptions))).
+
+%!  button_classes(+ElemOptions, +FormOptions)//
+%
+%   Collect the classes from element and form options
+
+button_classes(IOptions, Options) -->
+    button_type_class(IOptions),
+    button_size_class(IOptions, Options).
+
+button_type_class(IOptions) -->
+    { option(type(Type), IOptions),
+      !,
+      atom_concat('btn-', Type, Class)
+    },
+    [Class].
+button_type_class(_IOptions) -->
+    ['btn-default'].
+
+button_size_class(IOptions, Options) -->
+    { (   option(button_size(Size), IOptions)
+      ;   option(button_size(Size), Options)
+      ),
+      !,
+      atom_concat('btn-', Size, Class)
+    },
+    [Class].
+button_size_class(_IOptions, _Options) -->
+    [].
+
+%!  data(+Options)//
+%
+%   Collect data options.
+
+data(Options) -->
+    { option(data(Data), Options, []) },
+    !,
+    data_values(Data).
+data(_) --> [].
+
+data_values([]) --> !.
+data_values([H|T]) --> !, data_values(H), data_values(T).
+data_values(Name-Value) -->
+    !,
+    data_value(Name, Value).
+data_values(Name=Value) -->
+    !,
+    data_value(Name, Value).
+data_values(NameValue) -->
+    { NameValue =.. [Name,Value] },
+    data_value(Name, Value).
+
+data_value(Name, Value) -->
+    { atom_concat('data-', Name, AttrName),
+      Attr =.. [AttrName,Value]
+    },
+    [Attr].
+
+%!  classes(+Options)//
+%
+%   Collect defined classes
+
+classes([]) --> !.
+classes([class(Classes)|T]) --> !, class(Classes), classes(T).
+classes([_|T]) --> classes(T).
+
+class([]) --> !.
+class([H|T]) --> !, class(H), class(T).
+class(Class) --> [Class].
+
+
+		 /*******************************
+		 *            UTIL		*
+		 *******************************/
+
+label(Name, Options) -->
+    { (   option(label(Label), Options)
+      ->  true
+      ;   name_label(Name, Label)
+      )
+    },
+    html(Label).
+
+%!  name_label(+Name, -Label) is det.
+%
+%   Determine a label from a name by   upcasing  the first character and
+%   replacing all underscores by spaces.
+
+name_label(Name, Label) :-
+    atom_codes(Name, Codes),
+    phrase(name_label(up, LCodes), Codes),
+    atom_codes(Label, LCodes).
+
+name_label(up,   [H|T])    --> [H0], !, {code_type(H, to_upper(H0))}, name_label(keep, T).
+name_label(keep, [0'\s|T]) --> "_",  !, name_label(keep, T).
+name_label(keep, [H|T])    --> [H],  !, name_label(keep, T).
+name_label(_,    [])       --> [].
diff --git a/lib/swish/chat.pl b/lib/swish/chat.pl
new file mode 100644
index 0000000..b6148c0
--- /dev/null
+++ b/lib/swish/chat.pl
@@ -0,0 +1,1210 @@
+/*  Part of SWISH
+
+    Author:        Jan Wielemaker
+    E-mail:        J.Wielemaker@cs.vu.nl
+    WWW:           http://www.swi-prolog.org
+    Copyright (C): 2016-2017, VU University Amsterdam
+			      CWI Amsterdam
+    All rights reserved.
+
+    Redistribution and use in source and binary forms, with or without
+    modification, are permitted provided that the following conditions
+    are met:
+
+    1. Redistributions of source code must retain the above copyright
+       notice, this list of conditions and the following disclaimer.
+
+    2. Redistributions in binary form must reproduce the above copyright
+       notice, this list of conditions and the following disclaimer in
+       the documentation and/or other materials provided with the
+       distribution.
+
+    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
+    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
+    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
+    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
+    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
+    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
+    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
+    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
+    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
+    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
+    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
+    POSSIBILITY OF SUCH DAMAGE.
+*/
+
+:- module(swish_chat,
+	  [ chat_broadcast/1,		% +Message
+	    chat_broadcast/2,		% +Message, +Channel
+	    chat_to_profile/2,		% +ProfileID, :HTML
+	    chat_about/2,		% +DocID, +Message
+
+	    notifications//1		% +Options
+	  ]).
+:- use_module(library(http/hub)).
+:- use_module(library(http/http_dispatch)).
+:- use_module(library(http/http_session)).
+:- use_module(library(http/http_parameters)).
+:- use_module(library(http/websocket)).
+:- use_module(library(http/json)).
+:- use_module(library(error)).
+:- use_module(library(lists)).
+:- use_module(library(option)).
+:- use_module(library(debug)).
+:- use_module(library(uuid)).
+:- use_module(library(random)).
+:- use_module(library(base64)).
+:- use_module(library(apply)).
+:- use_module(library(broadcast)).
+:- use_module(library(ordsets)).
+:- use_module(library(http/html_write)).
+:- use_module(library(http/http_path)).
+:- if(exists_source(library(user_profile))).
+:- use_module(library(user_profile)).
+:- endif.
+:- use_module(library(aggregate)).
+
+:- use_module(storage).
+:- use_module(gitty).
+:- use_module(config).
+:- use_module(avatar).
+:- use_module(noble_avatar).
+:- use_module(chatstore).
+:- use_module(authenticate).
+:- use_module(pep).
+
+:- html_meta(chat_to_profile(+, html)).
+
+/** <module> The SWISH collaboration backbone
+
+We have three levels of identity as   enumerated  below. Note that these
+form a hierarchy: a particular user  may   be  logged  on using multiple
+browsers which in turn may have multiple SWISH windows opened.
+
+  1. Any open SWISH window has an associated websocket, represented
+     by the identifier returned by hub_add/3.
+  2. Any browser, possibly having multiple open SWISH windows, is
+     identified by a session cookie.
+  3. The user may be logged in, either based on the cookie or on
+     HTTP authentication.
+*/
+
+		 /*******************************
+		 *	ESTABLISH WEBSOCKET	*
+		 *******************************/
+
+:- http_handler(swish(chat), start_chat, [ id(swish_chat) ]).
+
+:- meta_predicate must_succeed(0).
+
+%!	start_chat(+Request)
+%
+%	HTTP handler that establishes  a   websocket  connection where a
+%	user gets an avatar and optionally a name.
+
+start_chat(Request) :-
+	authenticate(Request, Identity),
+	start_chat(Request, [identity(Identity)]).
+
+start_chat(Request, Options) :-
+	authorized(chat, Options),
+	(   http_in_session(Session)
+	->  CheckLogin = false
+	;   http_open_session(Session, []),
+	    CheckLogin = true
+	),
+	check_flooding,
+	http_parameters(Request,
+			[ avatar(Avatar, [optional(true)]),
+			  nickname(NickName, [optional(true)]),
+			  reconnect(Token, [optional(true)])
+			]),
+	extend_options([ avatar(Avatar),
+			 nick_name(NickName),
+			 reconnect(Token),
+			 check_login(CheckLogin)
+		       ], Options, ChatOptions),
+	http_upgrade_to_websocket(
+	    accept_chat(Session, ChatOptions),
+	    [ guarded(false),
+	      subprotocols(['v1.chat.swish.swi-prolog.org', chat])
+	    ],
+	    Request).
+
+extend_options([], Options, Options).
+extend_options([H|T0], Options, [H|T]) :-
+	ground(H), !,
+	extend_options(T0, Options, T).
+extend_options([_|T0], Options, T) :-
+	extend_options(T0, Options, T).
+
+
+%!	check_flooding
+%
+%	See whether the client associated with  a session is flooding us
+%	and if so, return a resource error.
+
+check_flooding :-
+	get_time(Now),
+	(   http_session_retract(websocket(Score, Last))
+	->  Passed is Now-Last,
+	    NewScore is Score*(2**(-Passed/60)) + 10
+	;   NewScore = 10,
+	    Passed = 0
+	),
+	http_session_assert(websocket(NewScore, Now)),
+	(   NewScore > 50
+	->  throw(http_reply(resource_error(
+				 websocket(reconnect(Passed, NewScore)))))
+	;   true
+	).
+
+%!	accept_chat(+Session, +Options, +WebSocket)
+
+accept_chat(Session, Options, WebSocket) :-
+	must_succeed(accept_chat_(Session, Options, WebSocket)).
+
+accept_chat_(Session, Options, WebSocket) :-
+	create_chat_room,
+	(   reconnect_token(WSID, Token, Options),
+	    retractall(visitor_status(WSID, lost(_))),
+	    existing_visitor(WSID, Session, Token, TmpUser, UserData),
+	    hub_add(swish_chat, WebSocket, WSID)
+	->  Reason = rejoined
+	;   hub_add(swish_chat, WebSocket, WSID),
+	    must_succeed(create_visitor(WSID, Session, Token,
+					TmpUser, UserData, Options)),
+	    Reason = joined
+	),
+	visitor_count(Visitors),
+	option(check_login(CheckLogin), Options, true),
+	Msg = _{ type:welcome,
+		 uid:TmpUser,
+		 wsid:WSID,
+		 reconnect:Token,
+		 visitors:Visitors,
+		 check_login:CheckLogin
+	       },
+	hub_send(WSID, json(UserData.put(Msg))),
+	must_succeed(chat_broadcast(UserData.put(_{type:Reason,
+						   visitors:Visitors,
+						   wsid:WSID}))),
+	gc_visitors.
+
+reconnect_token(WSID, Token, Options) :-
+	option(reconnect(Token), Options),
+	visitor_session(WSID, _, Token), !.
+
+must_succeed(Goal) :-
+	catch(Goal, E, print_message(warning, E)), !.
+must_succeed(Goal) :-
+	print_message(warning, goal_failed(Goal)).
+
+
+		 /*******************************
+		 *	        DATA		*
+		 *******************************/
+
+%%	visitor_session(?WSId, ?Session, ?Token).
+%%	session_user(?Session, ?TmpUser).
+%%	visitor_data(?TmpUser, ?UserData:dict).
+%%	subscription(?Session, ?Channel, ?SubChannel).
+%
+%	These predicates represent our notion of visitors.
+%
+%	@arg WSID is the identifier of the web socket. As we may have to
+%	reconnect lost connections, this is may be replaced.
+%	@arg Session is the session identifier.  This is used to connect
+%	SWISH actions to WSIDs.
+%	@arg TmpUser is the ID with which we identify the user for this
+%	run. The value is a UUID and thus doesn't reveal the real
+%	identity of the user.
+%	@arg UserDict is a dict that holds information about the real
+%	user identity.  This can be empty if no information is known
+%	about this user.
+
+:- dynamic
+	visitor_status/2,		% WSID, Status
+	visitor_session/3,		% WSID, Session, Token
+	session_user/2,			% Session, TmpUser
+	visitor_data/2,			% TmpUser, Data
+	subscription/3.			% WSID, Channel, SubChannel
+
+%!	visitor(?WSID) is nondet
+%
+%	True when WSID should be considered an active visitor.
+
+visitor(WSID) :-
+	visitor_session(WSID, _Session, _Token),
+	\+ inactive(WSID, 30).
+
+visitor_count(Count) :-
+	aggregate_all(count, visitor(_), Count).
+
+%!	inactive(+WSID, +Timeout) is semidet.
+%
+%	True if WSID is inactive. This means   we lost the connection at
+%	least Timeout seconds ago.
+
+inactive(WSID, Timeout) :-
+	visitor_status(WSID, lost(Lost)),
+	get_time(Now),
+	Now - Lost > Timeout.
+
+%!	visitor_session(?WSID, ?Session) is nondet.
+%
+%	True if websocket WSID is associated with Session.
+
+visitor_session(WSID, Session) :-
+	visitor_session(WSID, Session, _Token).
+
+%!	wsid_visitor(?WSID, ?Visitor)
+%
+%	True when WSID is associated with Visitor
+
+wsid_visitor(WSID, Visitor) :-
+	nonvar(WSID), !,
+	visitor_session(WSID, Session),
+	session_user(Session, Visitor).
+wsid_visitor(WSID, Visitor) :-
+	session_user(Session, Visitor),
+	visitor_session(WSID, Session).
+
+
+%!	existing_visitor(+WSID, +Session, +Token, -TmpUser, -UserData) is semidet.
+%
+%	True if we are dealing with  an   existing  visitor for which we
+%	lost the connection.
+
+existing_visitor(WSID, Session, Token, TmpUser, UserData) :-
+	visitor_session(WSID, Session, Token),
+	session_user(Session, TmpUser),
+	visitor_data(TmpUser, UserData), !.
+existing_visitor(WSID, Session, Token, _, _) :-
+	retractall(visitor_session(WSID, Session, Token)),
+	fail.
+
+%%	create_visitor(+WSID, +Session, ?Token, -TmpUser, -UserData, +Options)
+%
+%	Create a new visitor  when  a   new  websocket  is  established.
+%	Options provides information we have about the user:
+%
+%	  - current_user_info(+Info)
+%	  Already logged in user with given information
+%	  - avatar(Avatar)
+%	  Avatar remembered in the browser for this user.
+%	  - nick_name(NickName)
+%	  Nick name remembered in the browser for this user.
+
+create_visitor(WSID, Session, Token, TmpUser, UserData, Options) :-
+	generate_key(Token),
+	assertz(visitor_session(WSID, Session, Token)),
+	create_session_user(Session, TmpUser, UserData, Options).
+
+%!  generate_key(-Key) is det.
+%
+%   Generate a random confirmation key
+
+generate_key(Key) :-
+	length(Codes, 16),
+	maplist(random_between(0,255), Codes),
+	phrase(base64url(Codes), Encoded),
+	atom_codes(Key, Encoded).
+
+%%	destroy_visitor(+WSID)
+%
+%	The web socket WSID has been   closed. We should not immediately
+%	destroy the temporary user as the browser may soon reconnect due
+%	to a page reload  or  re-establishing   the  web  socket after a
+%	temporary network failure. We leave   the destruction thereof to
+%	the session, but set the session timeout to a fairly short time.
+%
+%	@tbd	We should only inform clients that we have informed
+%		about this user.
+
+destroy_visitor(WSID) :-
+	must_be(atom, WSID),
+	destroy_reason(WSID, Reason),
+	(   Reason == unload
+	->  reclaim_visitor(WSID)
+	;   get_time(Now),
+	    assertz(visitor_status(WSID, lost(Now)))
+	),
+	visitor_count(Count),
+	chat_broadcast(_{ type:removeUser,
+			  wsid:WSID,
+			  reason:Reason,
+			  visitors:Count
+			}).
+
+destroy_reason(WSID, Reason) :-
+	retract(visitor_status(WSID, unload)), !,
+	Reason = unload.
+destroy_reason(_, close).
+
+%!	gc_visitors
+%
+%	Reclaim all visitors with whom we   have lost the connection and
+%	the browser did not reclaim the selection within 5 minutes.
+
+:- dynamic last_gc/1.
+
+gc_visitors :-
+	last_gc(Last),
+	get_time(Now),
+	Now-Last < 300, !.
+gc_visitors :-
+	with_mutex(gc_visitors, gc_visitors_sync).
+
+gc_visitors_sync :-
+	get_time(Now),
+	(   last_gc(Last),
+	    Now-Last < 300
+	->  true
+	;   retractall(last_gc(_)),
+	    asserta(last_gc(Now)),
+	    do_gc_visitors
+	).
+
+do_gc_visitors :-
+	forall(( visitor_session(WSID, _Session, _Token),
+		 inactive(WSID, 5*60)
+	       ),
+	       reclaim_visitor(WSID)).
+
+reclaim_visitor(WSID) :-
+	debug(chat(gc), 'Reclaiming idle ~p', [WSID]),
+	retractall(visitor_session(WSID, _Session, _Token)),
+	retractall(visitor_status(WSID, _Status)),
+	unsubscribe(WSID, _).
+
+
+%%	create_session_user(+Session, -User, -UserData, +Options)
+%
+%	Associate a user with the session. The user id is a UUID that is
+%	not associated with  any  persistent  notion   of  a  user.  The
+%	destruction is left to the destruction of the session.
+
+:- listen(http_session(end(SessionID, _Peer)),
+	  destroy_session_user(SessionID)).
+
+create_session_user(Session, TmpUser, UserData, _Options) :-
+	session_user(Session, TmpUser),
+	visitor_data(TmpUser, UserData), !.
+create_session_user(Session, TmpUser, UserData, Options) :-
+	uuid(TmpUser),
+	get_visitor_data(UserData, Options),
+	assertz(session_user(Session, TmpUser)),
+	assertz(visitor_data(TmpUser, UserData)).
+
+destroy_session_user(Session) :-
+	forall(visitor_session(WSID, Session, _Token),
+	       inform_session_closed(WSID, Session)),
+	retractall(visitor_session(_, Session, _)),
+	forall(retract(session_user(Session, TmpUser)),
+	       destroy_visitor_data(TmpUser)).
+
+destroy_visitor_data(TmpUser) :-
+	(   retract(visitor_data(TmpUser, Data)),
+	    release_avatar(Data.get(avatar)),
+	    fail
+	;   true
+	).
+
+inform_session_closed(WSID, Session) :-
+	ignore(hub_send(WSID, json(_{type:session_closed}))),
+	session_user(Session, TmpUser),
+	update_visitor_data(TmpUser, _Data, logout).
+
+
+%!	update_visitor_data(+TmpUser, +Data, +Reason) is det.
+%
+%	Update the user data for the visitor   TmpUser  to Data. This is
+%	rather complicates due to all the   defaulting  rules. Reason is
+%	one of:
+%
+%	  - login
+%	  - logout
+%	  - 'set-nick-name'
+%	  - 'profile-edit'
+%
+%	@tbd Create a more declarative description  on where the various
+%	attributes must come from.
+
+update_visitor_data(TmpUser, _Data, logout) :- !,
+	anonymise_user_data(TmpUser, NewData),
+	set_visitor_data(TmpUser, NewData, logout).
+update_visitor_data(TmpUser, Data, Reason) :-
+	profile_reason(Reason), !,
+	(   visitor_data(TmpUser, Old)
+	;   Old = v{}
+	),
+	copy_profile([name,avatar,email], Data, Old, New),
+	set_visitor_data(TmpUser, New, Reason).
+update_visitor_data(TmpUser, _{name:Name}, 'set-nick-name') :- !,
+	visitor_data(TmpUser, Old),
+	set_nick_name(Old, Name, New),
+	set_visitor_data(TmpUser, New, 'set-nick-name').
+update_visitor_data(TmpUser, Data, Reason) :-
+	set_visitor_data(TmpUser, Data, Reason).
+
+profile_reason('profile-edit').
+profile_reason('login').
+
+copy_profile([], _, Data, Data).
+copy_profile([H|T], New, Data0, Data) :-
+	copy_profile_field(H, New, Data0, Data1),
+	copy_profile(T, New, Data1, Data).
+
+copy_profile_field(avatar, New, Data0, Data) :-	!,
+	(   Data1 = Data0.put(avatar,New.get(avatar))
+	->  Data  = Data1.put(avatar_source, profile)
+	;   email_gravatar(New.get(email), Avatar),
+	    valid_gravatar(Avatar)
+	->  Data = Data0.put(_{avatar:Avatar,avatar_source:email})
+	;   Avatar = Data0.get(anonymous_avatar)
+	->  Data = Data0.put(_{avatar:Avatar,avatar_source:client})
+	;   noble_avatar_url(Avatar, []),
+	    Data = Data0.put(_{avatar:Avatar,avatar_source:generated,
+			       anonymous_avatar:Avatar
+			      })
+	).
+copy_profile_field(email, New, Data0, Data) :- !,
+	(   NewMail = New.get(email)
+	->  update_avatar_from_email(NewMail, Data0, Data1),
+	    Data = Data1.put(email, NewMail)
+	;   update_avatar_from_email('', Data0, Data1),
+	    (	del_dict(email, Data1, _, Data)
+	    ->	true
+	    ;	Data = Data1
+	    )
+	).
+copy_profile_field(F, New, Data0, Data) :-
+	(   Data = Data0.put(F, New.get(F))
+	->  true
+	;   del_dict(F, Data0, _, Data)
+	->  true
+	;   Data = Data0
+	).
+
+set_nick_name(Data0, Name, Data) :-
+	Data = Data0.put(_{name:Name, anonymous_name:Name}).
+
+%!	update_avatar_from_email(+Email, +DataIn, -Data)
+%
+%	Update the avatar after a change  of   the  known  email. If the
+%	avatar comes from the profile, no action is needed. If Email has
+%	a gravatar, use that. Else  use  the   know  or  a new generated
+%	avatar.
+
+update_avatar_from_email(_, Data, Data) :-
+	Data.get(avatar_source) == profile, !.
+update_avatar_from_email('', Data0, Data) :-
+	Data0.get(avatar_source) == email, !,
+	noble_avatar_url(Avatar, []),
+	Data = Data0.put(_{avatar:Avatar, anonymous_avatar:Avatar,
+			   avatar_source:generated}).
+update_avatar_from_email(Email, Data0, Data) :-
+	email_gravatar(Email, Avatar),
+	valid_gravatar(Avatar), !,
+	Data = Data0.put(avatar, Avatar).
+update_avatar_from_email(_, Data0, Data) :-
+	(   Avatar = Data0.get(anonymous_avatar)
+	->  Data = Data0.put(_{avatar:Avatar, avatar_source:client})
+	;   noble_avatar_url(Avatar, []),
+	    Data = Data0.put(_{avatar:Avatar, anonymous_avatar:Avatar,
+			       avatar_source:generated})
+	).
+
+%!	anonymise_user_data(TmpUser, Data)
+%
+%	Create anonymous user profile.
+
+anonymise_user_data(TmpUser, Data) :-
+	visitor_data(TmpUser, Old),
+	(   _{anonymous_name:AName, anonymous_avatar:AAvatar} :< Old
+	->  Data = _{anonymous_name:AName, anonymous_avatar:AAvatar,
+		     name:AName, avatar:AAvatar, avatar_source:client}
+	;   _{anonymous_avatar:AAvatar} :< Old
+	->  Data = _{anonymous_avatar:AAvatar,
+		     avatar:AAvatar, avatar_source:client}
+	;   _{anonymous_name:AName} :< Old
+	->  noble_avatar_url(Avatar, []),
+	    Data = _{anonymous_name:AName, anonymous_avatar:Avatar,
+		     name:AName, avatar:Avatar, avatar_source:generated}
+	), !.
+anonymise_user_data(_, Data) :-
+	noble_avatar_url(Avatar, []),
+	Data = _{anonymous_avatar:Avatar,
+		 avatar:Avatar, avatar_source:generated}.
+
+%!	set_visitor_data(+TmpUser, +Data, +Reason) is det.
+%
+%	Update the user data for the   session  user TmpUser and forward
+%	the changes.
+
+set_visitor_data(TmpUser, Data, Reason) :-
+	retractall(visitor_data(TmpUser, _)),
+	assertz(visitor_data(TmpUser, Data)),
+	inform_visitor_change(TmpUser, Reason).
+
+%!	inform_visitor_change(+TmpUser, +Reason) is det.
+%
+%	Inform browsers showing  TmpUser  that   the  visitor  data  has
+%	changed. The first  clause  deals   with  forwarding  from  HTTP
+%	requests,  where  we  have  the  session  and  the  second  from
+%	websocket requests where we have the WSID.
+
+inform_visitor_change(TmpUser, Reason) :-
+	http_in_session(Session), !,
+	public_user_data(TmpUser, Data),
+	forall(visitor_session(WSID, Session),
+	       inform_friend_change(WSID, Data, Reason)).
+inform_visitor_change(TmpUser, Reason) :-
+	b_getval(wsid, WSID),
+	public_user_data(TmpUser, Data),
+	inform_friend_change(WSID, Data, Reason).
+
+inform_friend_change(WSID, Data, Reason) :-
+	Message = json(_{ type:"profile",
+			  wsid:WSID,
+			  reason:Reason
+			}.put(Data)),
+	hub_send(WSID, Message),
+	forall(viewing_same_file(WSID, Friend),
+	       ignore(hub_send(Friend, Message))).
+
+viewing_same_file(WSID, Friend) :-
+	subscription(WSID, gitty, File),
+	subscription(Friend, gitty, File),
+	Friend \== WSID.
+
+%%	subscribe(+WSID, +Channel) is det.
+
+subscribe(WSID, Channel) :-
+	subscribe(WSID, Channel, _SubChannel).
+subscribe(WSID, Channel, SubChannel) :-
+	(   subscription(WSID, Channel, SubChannel)
+	->  true
+	;   assertz(subscription(WSID, Channel, SubChannel))
+	).
+
+unsubscribe(WSID, Channel) :-
+	unsubscribe(WSID, Channel, _SubChannel).
+unsubscribe(WSID, Channel, SubChannel) :-
+	retractall(subscription(WSID, Channel, SubChannel)).
+
+%%	sync_gazers(+WSID, +Files:list(atom)) is det.
+%
+%	A browser signals it has Files open.   This happens when a SWISH
+%	instance is created as well  as   when  a SWISH instance changes
+%	state, such as closing a tab, adding   a  tab, bringing a tab to
+%	the foreground, etc.
+
+sync_gazers(WSID, Files0) :-
+	findall(F, subscription(WSID, gitty, F), Viewing0),
+	sort(Files0, Files),
+	sort(Viewing0, Viewing),
+	(   Files == Viewing
+	->  true
+	;   ord_subtract(Files, Viewing, New),
+	    add_gazing(WSID, New),
+	    ord_subtract(Viewing, Files, Left),
+	    del_gazing(WSID, Left)
+	).
+
+add_gazing(_, []) :- !.
+add_gazing(WSID, Files) :-
+	inform_me_about_existing_gazers(WSID, Files),
+	inform_existing_gazers_about_newby(WSID, Files).
+
+inform_me_about_existing_gazers(WSID, Files) :-
+	findall(Gazer, files_gazer(Files, Gazer), Gazers),
+	ignore(hub_send(WSID, json(_{type:"gazers", gazers:Gazers}))).
+
+files_gazer(Files, Gazer) :-
+	member(File, Files),
+	subscription(WSID, gitty, File),
+	visitor_session(WSID, Session),
+	session_user(Session, UID),
+	public_user_data(UID, Data),
+	Gazer = _{file:File, uid:UID, wsid:WSID}.put(Data).
+
+inform_existing_gazers_about_newby(WSID, Files) :-
+	forall(member(File, Files),
+	       signal_gazer(WSID, File)).
+
+signal_gazer(WSID, File) :-
+	subscribe(WSID, gitty, File),
+	broadcast_event(opened(File), File, WSID).
+
+del_gazing(_, []) :- !.
+del_gazing(WSID, Files) :-
+	forall(member(File, Files),
+	       del_gazing1(WSID, File)).
+
+del_gazing1(WSID, File) :-
+	broadcast_event(closed(File), File, WSID),
+	unsubscribe(WSID, gitty, File).
+
+%%	add_user_details(+Message, -Enriched) is det.
+%
+%	Add additional information to a message.  Message must
+%	contain a `uid` field.
+
+add_user_details(Message, Enriched) :-
+	public_user_data(Message.uid, Data),
+	Enriched = Message.put(Data).
+
+%%	public_user_data(+UID, -Public:dict) is det.
+%
+%	True when Public provides the   information  we publically share
+%	about UID. This is currently the name and avatar.
+
+public_user_data(UID, Public) :-
+	visitor_data(UID, Data),
+	(   _{name:Name, avatar:Avatar} :< Data
+	->  Public = _{name:Name, avatar:Avatar}
+	;   _{avatar:Avatar} :< Data
+	->  Public = _{avatar:Avatar}
+	;   Public = _{}
+	).
+
+%%	get_visitor_data(-Data:dict, +Options) is det.
+%
+%	Optain data for a new visitor.  Options include:
+%
+%	  - identity(+Identity)
+%	  Identity information provided by authenticate/2.  Always
+%	  present.
+%	  - avatar(+URL)
+%	  Avatar provided by the user
+%	  - nick_name(+Name)
+%	  Nick name provided by the user.
+%
+%	Data always contains an `avatar` key   and optionally contains a
+%	`name` and `email` key. If the avatar is generated there is also
+%	a key `avatar_generated` with the value `true`.
+%
+%	@bug	This may check for avatar validity, which may take
+%		long.  Possibly we should do this in a thread.
+
+get_visitor_data(Data, Options) :-
+	option(identity(Identity), Options),
+	findall(N-V, visitor_property(Identity, Options, N, V), Pairs),
+	dict_pairs(Data, v, Pairs).
+
+visitor_property(Identity, Options, name, Name) :-
+	(   user_property(Identity, name(Name))
+	->  true
+	;   option(nick_name(Name), Options)
+	).
+visitor_property(Identity, _, email, Email) :-
+	user_property(Identity, email(Email)).
+visitor_property(Identity, Options, Name, Value) :-
+	(   user_property(Identity, avatar(Avatar))
+	->  avatar_property(Avatar, profile, Name, Value)
+	;   user_property(Identity, email(Email)),
+	    email_gravatar(Email, Avatar),
+	    valid_gravatar(Avatar)
+	->  avatar_property(Avatar, email, Name, Value)
+	;   option(avatar(Avatar), Options)
+	->  avatar_property(Avatar, client, Name, Value)
+	;   noble_avatar_url(Avatar, Options),
+	    avatar_property(Avatar, generated, Name, Value)
+	).
+visitor_property(_, Options, anonymous_name, Name) :-
+	option(nick_name(Name), Options).
+visitor_property(_, Options, anonymous_avatar, Avatar) :-
+	option(avatar(Avatar), Options).
+
+
+avatar_property(Avatar, _Source, avatar,        Avatar).
+avatar_property(_Avatar, Source, avatar_source, Source).
+
+
+		 /*******************************
+		 *	   NOBLE AVATAR		*
+		 *******************************/
+
+:- http_handler(swish('avatar/'), reply_avatar, [id(avatar), prefix]).
+
+%%	reply_avatar(+Request)
+%
+%	HTTP handler for Noble  Avatar   images.  Using  create_avatar/2
+%	re-creates avatars from the file name,  so we can safely discard
+%	the avatar file store.
+
+reply_avatar(Request) :-
+	option(path_info(Local), Request),
+	(   absolute_file_name(noble_avatar(Local), Path,
+			       [ access(read),
+				 file_errors(fail)
+			       ])
+	->  true
+	;   create_avatar(Local, Path)
+	),
+	http_reply_file(Path, [unsafe(true)], Request).
+
+
+noble_avatar_url(HREF, Options) :-
+	option(avatar(HREF), Options), !.
+noble_avatar_url(HREF, _Options) :-
+	noble_avatar(_Gender, Path, true),
+	file_base_name(Path, File),
+	http_absolute_location(swish(avatar/File), HREF, []).
+
+
+		 /*******************************
+		 *	   BROADCASTING		*
+		 *******************************/
+
+%%	chat_broadcast(+Message)
+%%	chat_broadcast(+Message, +Channel)
+%
+%	Send Message to all known SWISH clients. Message is a valid JSON
+%	object, i.e., a dict or option list.
+%
+%	@arg Channel is either an atom or a term Channel/SubChannel,
+%	where both Channel and SubChannel are atoms.
+
+chat_broadcast(Message) :-
+	debug(chat(broadcast), 'Broadcast: ~p', [Message]),
+	hub_broadcast(swish_chat, json(Message)).
+
+chat_broadcast(Message, Channel/SubChannel) :- !,
+	must_be(atom, Channel),
+	must_be(atom, SubChannel),
+	debug(chat(broadcast), 'Broadcast on ~p: ~p',
+	      [Channel/SubChannel, Message]),
+	hub_broadcast(swish_chat, json(Message),
+		      subscribed(Channel, SubChannel)).
+chat_broadcast(Message, Channel) :-
+	must_be(atom, Channel),
+	debug(chat(broadcast), 'Broadcast on ~p: ~p', [Channel, Message]),
+	hub_broadcast(swish_chat, json(Message),
+		      subscribed(Channel)).
+
+subscribed(Channel, WSID) :-
+	subscription(WSID, Channel, _).
+subscribed(Channel, SubChannel, WSID) :-
+	subscription(WSID, Channel, SubChannel).
+
+
+		 /*******************************
+		 *	     CHAT ROOM		*
+		 *******************************/
+
+create_chat_room :-
+	current_hub(swish_chat, _), !.
+create_chat_room :-
+	with_mutex(swish_chat, create_chat_room_sync).
+
+create_chat_room_sync :-
+	current_hub(swish_chat, _), !.
+create_chat_room_sync :-
+	hub_create(swish_chat, Room, _{}),
+	thread_create(swish_chat(Room), _, [alias(swish_chat)]).
+
+swish_chat(Room) :-
+	(   catch(swish_chat_event(Room), E, chat_exception(E))
+	->  true
+	;   print_message(warning, goal_failed(swish_chat_event(Room)))
+	),
+	swish_chat(Room).
+
+chat_exception('$aborted') :- !.
+chat_exception(E) :-
+	print_message(warning, E).
+
+swish_chat_event(Room) :-
+	thread_get_message(Room.queues.event, Message),
+	(   handle_message(Message, Room)
+	->  true
+	;   print_message(warning, goal_failed(handle_message(Message, Room)))
+	).
+
+%%	handle_message(+Message, +Room)
+%
+%	Handle incoming messages
+
+handle_message(Message, _Room) :-
+	websocket{opcode:text} :< Message, !,
+	atom_json_dict(Message.data, JSON, []),
+	debug(chat(received), 'Received from ~p: ~p', [Message.client, JSON]),
+	WSID = Message.client,
+	setup_call_cleanup(
+	    b_setval(wsid, WSID),
+	    json_message(JSON, WSID),
+	    nb_delete(wsid)).
+handle_message(Message, _Room) :-
+	hub{joined:WSID} :< Message, !,
+	debug(chat(visitor), 'Joined: ~p', [WSID]).
+handle_message(Message, _Room) :-
+	hub{left:WSID, reason:write(Lost)} :< Message, !,
+	(   destroy_visitor(WSID)
+	->  debug(chat(visitor), 'Left ~p due to write error for ~p',
+		  [WSID, Lost])
+	;   true
+	).
+handle_message(Message, _Room) :-
+	hub{left:WSID} :< Message, !,
+	(   destroy_visitor(WSID)
+	->  debug(chat(visitor), 'Left: ~p', [WSID])
+	;   true
+	).
+handle_message(Message, _Room) :-
+	websocket{opcode:close, client:WSID} :< Message, !,
+	debug(chat(visitor), 'Left: ~p', [WSID]),
+	destroy_visitor(WSID).
+handle_message(Message, _Room) :-
+	debug(chat(ignored), 'Ignoring chat message ~p', [Message]).
+
+
+%%	json_message(+Message, +WSID) is det.
+%
+%	Process a JSON message  translated  to   a  dict.  The following
+%	messages are understood:
+%
+%	  - subscribe channel [subchannel]
+%	  - unsubscribe channel [subchannel]
+%	  Actively (un)subscribe for specific message channels.
+%	  - unload
+%	  A SWISH instance is cleanly being unloaded.
+%	  - has-open-files files
+%	  Executed after initiating the websocket to indicate loaded
+%	  files.
+%	  - set-nick-name name
+%	  User set nick name for anonymous identoty
+
+json_message(Dict, WSID) :-
+	_{ type: "subscribe",
+	   channel:ChannelS, sub_channel:SubChannelS} :< Dict, !,
+	atom_string(Channel, ChannelS),
+	atom_string(SubChannel, SubChannelS),
+	subscribe(WSID, Channel, SubChannel).
+json_message(Dict, WSID) :-
+	_{type: "subscribe", channel:ChannelS} :< Dict, !,
+	atom_string(Channel, ChannelS),
+	subscribe(WSID, Channel).
+json_message(Dict, WSID) :-
+	_{ type: "unsubscribe",
+	   channel:ChannelS, sub_channel:SubChannelS} :< Dict, !,
+	atom_string(Channel, ChannelS),
+	atom_string(SubChannel, SubChannelS),
+	unsubscribe(WSID, Channel, SubChannel).
+json_message(Dict, WSID) :-
+	_{type: "unsubscribe", channel:ChannelS} :< Dict, !,
+	atom_string(Channel, ChannelS),
+	unsubscribe(WSID, Channel).
+json_message(Dict, WSID) :-
+	_{type: "unload"} :< Dict, !,	% clean close/reload
+	sync_gazers(WSID, []),
+	assertz(visitor_status(WSID, unload)).
+json_message(Dict, WSID) :-
+	_{type: "has-open-files", files:FileDicts} :< Dict, !,
+	maplist(dict_file_name, FileDicts, Files),
+	sync_gazers(WSID, Files).
+json_message(Dict, WSID) :-
+	_{type: "reloaded", file:FileS, commit:Hash} :< Dict, !,
+	atom_string(File, FileS),
+	event_html(reloaded(File), HTML),
+	Message = _{ type:notify,
+		     wsid:WSID,
+		     html:HTML,
+		     event:reloaded,
+		     argv:[File,Hash]
+		   },
+	chat_broadcast(Message, gitty/File).
+json_message(Dict, WSID) :-
+	_{type: "set-nick-name", name:Name} :< Dict, !,
+	wsid_visitor(WSID, Visitor),
+	update_visitor_data(Visitor, _{name:Name}, 'set-nick-name').
+json_message(Dict, WSID) :-
+	_{type: "chat-message", docid:_} :< Dict, !,
+	chat_add_user_id(WSID, Dict, Message),
+	chat_relay(Message).
+json_message(Dict, _WSID) :-
+	debug(chat(ignored), 'Ignoring JSON message ~p', [Dict]).
+
+dict_file_name(Dict, File) :-
+	atom_string(File, Dict.get(file)).
+
+
+		 /*******************************
+		 *	   CHAT MESSAGES	*
+		 *******************************/
+
+%!	chat_add_user_id(+WSID, +Message0, -Message) is det.
+%
+%	Decorate a message with the user credentials.
+
+chat_add_user_id(WSID, Dict, Message) :-
+	visitor_session(WSID, Session, _Token),
+	session_user(Session, Visitor),
+	visitor_data(Visitor, UserData),
+	User0 = u{avatar:UserData.avatar,
+		  wsid:WSID
+		 },
+	(   Name = UserData.get(name)
+	->  User1 = User0.put(name, Name)
+	;   User1 = User0
+	),
+	(   http_current_session(Session, profile_id(ProfileID))
+	->  User = User1.put(profile_id, ProfileID)
+	;   User = User1
+	),
+	Message = Dict.put(user, User).
+
+
+%!	chat_about(+DocID, +Message) is det.
+%
+%	Distribute a chat message about DocID.
+
+chat_about(DocID, Message) :-
+	chat_relay(Message.put(docid, DocID)).
+
+%!	chat_relay(+Message) is det.
+%
+%	Store and relay a chat message.
+
+chat_relay(Message) :-
+	chat_enrich(Message, Message1),
+	chat_send(Message1).
+
+%!	chat_enrich(+Message0, -Message) is det.
+%
+%	Add time and identifier to the chat message.
+
+chat_enrich(Message0, Message) :-
+	get_time(Now),
+	uuid(ID),
+	Message = Message0.put(_{time:Now, id:ID}).
+
+%!	chat_send(+Message)
+%
+%	Relay the chat message Message. If  the message has a `volatile`
+%	property it is broadcasted, but not stored.
+
+chat_send(Message) :-
+	atom_concat("gitty:", File, Message.docid),
+	broadcast(swish(chat(Message))),
+	(   Message.get(volatile) == true
+	->  true
+	;   chat_store(Message)
+	),
+	chat_broadcast(Message, gitty/File).
+
+
+		 /*******************************
+		 *	      EVENTS		*
+		 *******************************/
+
+:- unlisten(swish(_)),
+   listen(swish(Event), chat_event(Event)).
+
+%%	chat_event(+Event) is semidet.
+%
+%	Event happened inside SWISH.  Currently triggered events:
+%
+%	  - updated(+File, +From, +To)
+%	  File was updated from hash From to hash To.
+%	  - profile(+ProfileID)
+%	  Session was associated with user with profile ProfileID
+%	  - logout(+ProfileID)
+%	  User logged out. If the login was based on HTTP authentication
+%	  ProfileID equals `http`.
+
+chat_event(Event) :-
+	broadcast_event(Event),
+	http_session_id(Session),
+	debug(event, 'Event: ~p, session ~q', [Event, Session]),
+	event_file(Event, File), !,
+	(   visitor_session(WSID, Session),
+	    subscription(WSID, gitty, File)
+	->  true
+	;   visitor_session(WSID, Session)
+	->  true
+	;   WSID = undefined
+	),
+	session_broadcast_event(Event, File, Session, WSID).
+chat_event(logout(_ProfileID)) :- !,
+	http_session_id(Session),
+	session_user(Session, User),
+	update_visitor_data(User, _, logout).
+chat_event(visitor_count(Count)) :-		% request
+	visitor_count(Count).
+
+:- if(current_predicate(current_profile/2)).
+
+chat_event(profile(ProfileID)) :- !,
+	current_profile(ProfileID, Profile),
+	http_session_id(Session),
+	session_user(Session, User),
+	update_visitor_data(User, Profile, login).
+
+%!	propagate_profile_change(+ProfileID, +Attribute, +Value)
+%
+%	Trap external changes to the profile.
+
+:- listen(user_profile(modified(ProfileID, Name, _Old, New)),
+          propagate_profile_change(ProfileID, Name, New)).
+
+propagate_profile_change(ProfileID, _, _) :-
+	http_current_session(Session, profile_id(ProfileID)),
+	session_user(Session, User),
+	current_profile(ProfileID, Profile),
+	update_visitor_data(User, Profile, 'profile-edit').
+
+:- endif.
+
+%%	broadcast_event(+Event) is semidet.
+%
+%	If true, broadcast this event.
+
+broadcast_event(updated(_File, _From, _To)).
+
+
+%%	broadcast_event(+Event, +File, +WSID) is det.
+%
+%	Event happened that is related to File  in WSID. Broadcast it to
+%	subscribed users as a notification. Always succeeds, also if the
+%	message cannot be delivered.
+%
+%	@tbd	Extend the structure to allow other browsers to act.
+
+broadcast_event(Event, File, WSID) :-
+	visitor_session(WSID, Session),
+	session_broadcast_event(Event, File, Session, WSID), !.
+broadcast_event(_, _, _).
+
+session_broadcast_event(Event, File, Session, WSID) :-
+	session_user(Session, UID),
+	event_html(Event, HTML),
+	Event =.. [EventName|Argv],
+	Message0 = _{ type:notify,
+		      uid:UID,
+		      html:HTML,
+		      event:EventName,
+		      event_argv:Argv,
+		      wsid:WSID
+		    },
+	add_user_details(Message0, Message),
+	chat_broadcast(Message, gitty/File).
+
+%%	event_html(+Event, -HTML:string) mis det.
+%
+%	Describe an event as an HTML  message   to  be  displayed in the
+%	client's notification area.
+
+event_html(Event, HTML) :-
+	(   phrase(event_message(Event), Tokens)
+	->  true
+	;   phrase(html('Unknown-event: ~p'-[Event]), Tokens)
+	),
+	delete(Tokens, nl(_), SingleLine),
+	with_output_to(string(HTML), print_html(SingleLine)).
+
+event_message(created(File)) -->
+	html([ 'Created ', \file(File) ]).
+event_message(reloaded(File)) -->
+	html([ 'Reloaded ', \file(File) ]).
+event_message(updated(File, _From, _To)) -->
+	html([ 'Saved ', \file(File) ]).
+event_message(deleted(File, _From, _To)) -->
+	html([ 'Deleted ', \file(File) ]).
+event_message(closed(File)) -->
+	html([ 'Closed ', \file(File) ]).
+event_message(opened(File)) -->
+	html([ 'Opened ', \file(File) ]).
+event_message(download(File)) -->
+	html([ 'Opened ', \file(File) ]).
+event_message(download(Store, FileOrHash, _Format)) -->
+	{ event_file(download(Store, FileOrHash), File)
+	},
+	html([ 'Opened ', \file(File) ]).
+
+file(File) -->
+	html(a(href('/p/'+File), File)).
+
+%%	event_file(+Event, -File) is semidet.
+%
+%	True when Event is associated with File.
+
+event_file(created(File, _Commit), File).
+event_file(updated(File, _Commit), File).
+event_file(deleted(File, _Commit), File).
+event_file(download(Store, FileOrHash, _Format), File) :-
+	(   is_gitty_hash(FileOrHash)
+	->  gitty_commit(Store, FileOrHash, Meta),
+	    File = Meta.name
+	;   File = FileOrHash
+	).
+
+
+		 /*******************************
+		 *	   NOTIFICATION		*
+		 *******************************/
+
+%!	chat_to_profile(ProfileID, :HTML) is det.
+%
+%	Send a HTML notification to users logged in using ProfileID.
+
+chat_to_profile(ProfileID, HTML) :-
+	(   http_current_session(Session, profile_id(ProfileID)),
+	    visitor_session(WSID, Session),
+	    html_string(HTML, String),
+	    hub_send(WSID, json(_{ wsid:WSID,
+				   type:notify,
+				   html:String
+				 })),
+	    debug(notify(chat), 'Notify to ~p: ~p', [ProfileID, String]),
+	    fail
+	;   true
+	).
+
+html_string(HTML, String) :-
+	phrase(html(HTML), Tokens),
+	delete(Tokens, nl(_), SingleLine),
+	with_output_to(string(String), print_html(SingleLine)).
+
+
+
+
+		 /*******************************
+		 *	       UI		*
+		 *******************************/
+
+:- multifile swish_config:config/2.
+
+%%	notifications(+Options)//
+%
+%	The  chat  element  is  added  to  the  navbar  and  managed  by
+%	web/js/chat.js
+
+notifications(_Options) -->
+	{ swish_config:config(chat, true) }, !,
+	html(div(class(chat),
+		 [ div(class('chat-users'),
+		       ul([ class([nav, 'navbar-nav', 'pull-right']),
+			    id(chat)
+			  ], [])),
+		   div(class('user-count'),
+		       [ span(id('user-count'), '?'),
+			 ' users online'
+		       ])
+		 ])).
+notifications(_Options) -->
+	[].
+
+
+		 /*******************************
+		 *	      MESSAGES		*
+		 *******************************/
+
+:- multifile
+	prolog:message//1.
+
+prolog:message(websocket(reconnect(Passed, Score))) -->
+	[ 'WebSocket: too frequent reconnect requests (~1f sec; score = ~1f)'-
+	  [Passed, Score] ].
diff --git a/lib/swish/chatstore.pl b/lib/swish/chatstore.pl
new file mode 100644
index 0000000..a4323de
--- /dev/null
+++ b/lib/swish/chatstore.pl
@@ -0,0 +1,170 @@
+/*  Part of SWISH
+
+    Author:        Jan Wielemaker
+    E-mail:        J.Wielemaker@cs.vu.nl
+    WWW:           http://www.swi-prolog.org
+    Copyright (C): 2017, VU University Amsterdam
+			 CWI Amsterdam
+    All rights reserved.
+
+    Redistribution and use in source and binary forms, with or without
+    modification, are permitted provided that the following conditions
+    are met:
+
+    1. Redistributions of source code must retain the above copyright
+       notice, this list of conditions and the following disclaimer.
+
+    2. Redistributions in binary form must reproduce the above copyright
+       notice, this list of conditions and the following disclaimer in
+       the documentation and/or other materials provided with the
+       distribution.
+
+    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
+    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
+    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
+    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
+    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
+    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
+    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
+    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
+    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
+    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
+    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
+    POSSIBILITY OF SUCH DAMAGE.
+*/
+
+:- module(chat_store,
+          [ chat_store/1,               % +Message
+            chat_messages/2             % +DocID, -Messages
+          ]).
+:- use_module(library(settings)).
+:- use_module(library(filesex)).
+:- use_module(library(readutil)).
+:- use_module(library(sha)).
+:- use_module(library(http/http_dispatch)).
+:- use_module(library(http/http_parameters)).
+:- use_module(library(http/http_json)).
+
+:- http_handler(swish(chat/messages), chat_messages, [ id(chat_messages) ]).
+
+:- setting(directory, callable, data(chat),
+	   'The directory for storing chat messages.').
+
+/** <module> Store chat messages
+*/
+
+:- multifile
+    swish_config:chat_count_about/2.	% +DocID, -Count
+
+:- initialization open_chatstore.
+
+:- dynamic  storage_dir/1.
+:- volatile storage_dir/1.
+
+open_chatstore :-
+    setting(directory, Spec),
+    absolute_file_name(Spec, Dir,
+		       [ file_type(directory),
+			 access(write),
+			 file_errors(fail)
+		       ]), !,
+    asserta(storage_dir(Dir)).
+open_chatstore :-
+    setting(directory, Spec),
+    absolute_file_name(Spec, Dir,
+		       [ solutions(all)
+		       ]),
+    \+ exists_directory(Dir),
+    catch(make_directory(Dir),
+	  error(permission_error(create, directory, Dir), _),
+	  fail), !,
+    asserta(storage_dir(Dir)).
+
+chat_dir_file(DocID, Path, File) :-
+    sha_hash(DocID, Bin, []),
+    hash_atom(Bin, Hash),
+    sub_atom(Hash, 0, 2, _, D1),
+    sub_atom(Hash, 2, 2, _, D2),
+    sub_atom(Hash, 4, _, 0, Name),
+    storage_dir(Dir),
+    atomic_list_concat([Dir, D1, D2], /, Path),
+    atomic_list_concat([Path, Name], /, File).
+
+chat_file(DocID, File) :-
+    chat_dir_file(DocID, Dir, File),
+    make_directory_path(Dir).
+
+%!  chat_store(+Message:dict) is det.
+%
+%   Add a chat message to the chat  store. If `Message.create == false`,
+%   the message is only stored if the   chat  is already active. This is
+%   used to only insert messages about changes   to the file if there is
+%   an ongoing chat so we know to which version chat messages refer.
+
+chat_store(Message) :-
+    chat{docid:DocID} :< Message,
+    chat_file(DocID, File),
+    (	del_dict(create, Message, false, Message1)
+    ->	exists_file(File)
+    ;	Message1 = Message
+    ),
+    !,
+    strip_chat(Message1, Message2),
+    with_mutex(chat_store,
+               setup_call_cleanup(
+                   open(File, append, Out, [encoding(utf8)]),
+                   format(Out, '~q.~n', [Message2]),
+                   close(Out))).
+chat_store(_).
+
+%!  strip_chat(_Message0, -Message) is det.
+%
+%   Remove  stuff  from  a  chat  message   that  is  useless  to  store
+%   permanently, such as the wsid (WebSocket id).
+
+strip_chat(Message0, Message) :-
+    strip_chat_user(Message0.get(user), User),
+    !,
+    Message = Message0.put(user, User).
+strip_chat(Message, Message).
+
+strip_chat_user(User0, User) :-
+    del_dict(wsid, User0, _, User),
+    !.
+strip_chat_user(User, User).
+
+
+%!  chat_messages(+DocID, -Messages:list) is det.
+%
+%   Get all messages associated with DocID.
+
+chat_messages(DocID, Messages) :-
+    chat_dir_file(DocID, _, File),
+    (   exists_file(File)
+    ->  read_file_to_terms(File, Messages, [encoding(utf8)])
+    ;   Messages = []
+    ).
+
+%!  swish_config:chat_count_about(+DocID, -Count)
+%
+%   True when Count is the number of messages about DocID
+
+swish_config:chat_count_about(DocID, Count) :-
+    chat_messages(DocID, Messages),
+    length(Messages, Count).
+
+
+		 /*******************************
+		 *              HTTP		*
+		 *******************************/
+
+%!  chat_messages(+Request)
+%
+%   HTTP handler that returns chat messages for a document
+
+chat_messages(Request) :-
+    http_parameters(Request,
+                    [ docid(DocID, [])
+                    ]),
+    chat_messages(DocID, Messages),
+    reply_json_dict(Messages).
diff --git a/lib/swish/config.pl b/lib/swish/config.pl
index b27d22b..4799d63 100644
--- a/lib/swish/config.pl
+++ b/lib/swish/config.pl
@@ -45,7 +45,10 @@
 	config/2,			% ?Key, ?Value
 	config/3,			% ?Key, ?Value, +Options
 	source_alias/2,			% ?Alias, ?Options
-	authenticate/2.			% +Request, -User
+	authenticate/2,			% +Request, -User
+        login_item/2,                   % -Server, -HTML_DOM
+        login/2,                        % +Server, +Request
+        user_info/3.                    % +Request, -Server, -Info
 
 /** <module> Make HTTP locations known to JSON code
 */
@@ -135,6 +138,81 @@ swish_config(Key, Value, _) :-
 config(residuals_var, '_residuals').
 :- endif.
 
+		 /*******************************
+		 *             LOGIN		*
+		 *******************************/
+
+%!	login_item(-Server, -Item) is nondet.
+%
+%	This hook is called  to  find   all  possible  login options. It
+%	should bind Item to an HTML description for html//1 that must be
+%	clicked to login  with  this  option.   The  item  may  have the
+%	following HTML attributes:
+%
+%	  - 'data-server'(+Server)
+%	  This must be present and provides the first argument for the
+%	  login/2 hook.
+%
+%	  - 'data-frame'(+Style)
+%	  The login is realised in a popup to avoid reloading the
+%	  current swish page.  If Style is `popup`, a browser popup window
+%	  is used. This is necessary for identity providers that refuse to
+%	  open inside a frame. The default is `iframe`, which handles
+%	  the login inside an =iframe= element in a modal popup.
+%
+%	The Item is often  an  image.  The   image  must  have  a  class
+%	=login-with=. Below is an example to login with Google:
+%
+%	```
+%	swish_config:login_item(Item) :-
+%	    http_absolute_location(icons('social_google_box.png'), Img, []),
+%	    Item = img([ src(Img),
+%	                 class('login-with'),
+%	                 'data-server'(google),
+%	                 title('Login with Google')
+%	               ]).
+%	```
+%
+%	@arg Item may be of the form  `Tag-Item`. In this case the items
+%	are ordered by Tag. The default tag is `0`.
+
+%!	login(+Server, +Request) is det.
+%
+%	If a login item with   `'data-server'(+Server)`  is clicked, the
+%	HTTP handler with id `login` is called. This handler figures the
+%	selected login _server_ and calls this hook.
+
+%!	user_info(+Request, -Server, -UserInfo:dict) is semidet.
+%
+%	Each login facility must provide  this   hook.  The  hook should
+%	succeed if-and-only-if the user is logged in using this facility
+%	and the hook must bind UserInfo with   a  dict that contains the
+%	following fields:
+%
+%	  - user: User
+%	  User name (id) if the logged in user.
+%	  - name: Name
+%	  Common name of the logged in user.
+%	  - email: Email
+%	  Email address of the logged in user.
+%	  - picture: URL
+%	  If present, URL is used to indicate the currently logged in
+%	  user.
+%	  - auth_method: Method
+%	  Authentication method used. Currently one of `basic`, `digest`
+%	  or `oauth2`.
+%	  - logout_url: URL
+%	  URL that must be used to logout.  Needed if `auth_method` is
+%	  not one of the HTTP authentication methods (`basic` or
+%	  `digest`).
+%
+%	If this hook fails the user is not logged in.
+
+
+		 /*******************************
+		 *          OTHER HOOKS		*
+		 *******************************/
+
 %%	source_alias(?Alias, ?Options) is nondet.
 %
 %	Multifile hook that  defines   properties  of file_search_path/2
@@ -147,6 +225,7 @@ config(residuals_var, '_residuals').
 %	  given pattern in the matching directories.  Pattern is handed
 %	  to expand_file_name/2.
 
+
 		 /*******************************
 		 *	      MESSAGES		*
 		 *******************************/
diff --git a/lib/swish/cp_authenticate.pl b/lib/swish/cp_authenticate.pl
index 3bf6a89..3ca6da9 100644
--- a/lib/swish/cp_authenticate.pl
+++ b/lib/swish/cp_authenticate.pl
@@ -59,9 +59,11 @@ through pengine_user/1.
 swish_config:authenticate(_Request, User) :-
     logged_on(User).
 
-
 swish_config:user_info(_Request, local, Info) :-
     logged_on(User),
+    cp_user_info(User, Info).
+
+cp_user_info(User, Info) :-
     findall(Name-Value, cp_user_property(User, Name, Value), Pairs),
     dict_pairs(Info, u, Pairs).
 
@@ -87,3 +89,20 @@ cp_identity_property(Identity, Property) :-
     Property =.. [Name,Value],
     cp_user_property(User, Name, Value).
 
+
+		 /*******************************
+		 * LINK LOGIN/LOGOUT TO PROFILE *
+		 *******************************/
+
+:- listen(cliopatria(login(User, _Session)),
+          cp_logged_in(User)).
+:- listen(cliopatria(logout(User)),
+          cp_logged_out(User)).
+
+cp_logged_in(User) :-
+    cp_user_info(User, Info),
+    IdInfo = Info.put(_{identity_provider:local, external_identity:User}),
+    swish_config:reply_logged_in([user_info(IdInfo), reply(none)]).
+
+cp_logged_out(_User) :-
+    swish_config:reply_logged_out([reply(none)]).
diff --git a/lib/swish/examples.pl b/lib/swish/examples.pl
index 6f3ed90..781303a 100644
--- a/lib/swish/examples.pl
+++ b/lib/swish/examples.pl
@@ -3,7 +3,7 @@
     Author:        Jan Wielemaker
     E-mail:        J.Wielemaker@vu.nl
     WWW:           http://www.swi-prolog.org
-    Copyright (c)  2014-2015, VU University Amsterdam
+    Copyright (c)  2014-2017, VU University Amsterdam
     All rights reserved.
 
     Redistribution and use in source and binary forms, with or without
@@ -42,7 +42,7 @@
 :- use_module(library(lists)).
 :- use_module(library(settings)).
 
-:- use_module(gitty).
+:- use_module(storage).
 
 /** <module> Serve example files
 
@@ -149,9 +149,8 @@ storage_examples(List) :-
 storage_examples([]).
 
 gitty_example(json{title:Title, file:File, type:"store"}) :-
-	setting(web_storage:directory, Store),
-	gitty_file(Store, File, _),
-	gitty_commit(Store, File, Meta),
+	storage_file(File),
+	storage_meta_data(File, Meta),
 	Meta.get(example) == true,
 	(   Title = Meta.get(title), Title \== ""
 	->  true
diff --git a/lib/swish/form.pl b/lib/swish/form.pl
index 01719b5..c56af6b 100644
--- a/lib/swish/form.pl
+++ b/lib/swish/form.pl
@@ -85,12 +85,19 @@ validate_form([field(Field, Value, Options)|T], Dict, Errors) :-
 %	  All characters must be alphanumeric or spaces
 %	  - atom
 %	  Convert input to an atom
+%	  - string
+%	  Convert input to a string
 %	  - default(Term)
 %	  Use Term as value if no value appears in the input.
 %	  - downcase
 %	  Convert input to lower case
 %	  - email
 %	  Input must be a value E-mail address.
+%	  - url
+%	  Input must be a valid absolute URL
+%	  - url(Scheme)
+%	  Input must be a valid absolute URL of type Scheme. Using
+%	  `http` also allows for `https`
 %	  - float
 %	  Value is converted to a floating point number.
 %	  - integer
@@ -112,20 +119,33 @@ validate_form([field(Field, Value, Options)|T], Dict, Errors) :-
 %	  - strip
 %	  Strip leading and trailing white space and normalize
 %	  internal white space to a single space.
+%	  - term
+%	  Input is parsed as a Prolog term
 
 
 validate_field(Dict, Field, Value, Options) :-
-	(   Value0 = Dict.get(Field)
+	(   Value0 = Dict.get(Field),
+	    \+ is_empty(Value0)
 	->  validate_value(Options, Value0, Value, Field)
 	;   memberchk(default(Value), Options)
 	->  true
 	;   input_error(Field, required)
 	).
 
+is_empty(Value) :-
+	text(Value),
+	normalize_space(string(""), Value).
+
+text(Value) :- atom(Value), !.
+text(Value) :- string(Value).
+
 validate_value([], Value, Value, _).
 validate_value([H|T], Value0, Value, Field) :-
 	(   validate_step(H, Value0, Value1)
 	->  true
+	;   current_type(H, _, _),
+	    is_of_type(H, Value0)
+	->  Value1 = Value0
 	;   validate_failed(H, Value0, Field)
 	),
 	validate_value(T, Value1, Value, Field).
@@ -149,16 +169,27 @@ validate_step(length =< N, Value, Value) :-
 	Len =< N.
 validate_step(strip, Value0, Value) :-
 	normalize_space(string(Value), Value0).
+validate_step(term, Value0, Value) :-
+	term_string(Value, Value0).
 validate_step(alnum_and_spaces, Value, Value) :-
 	forall(sub_atom(Value, _, 1, _, Char),
 	       alnum_or_space(Char)).
 validate_step(email, Value, Value) :-
 	string_codes(Value, Codes),
 	phrase(email, Codes).
+validate_step(url, Value, Value) :-
+	validate_step(url(_), Value, Value).
+validate_step(url(Scheme), Value, Value) :-
+	is_url(Scheme, Value).
 validate_step(downcase, Value0, Value) :-
 	string_lower(Value0, Value).
 validate_step(atom, Value0, Value) :-
 	atom_string(Value, Value0).
+validate_step(string, Value0, Value) :-
+	(   string(Value0)
+	->  Value = Value0
+	;   atom_string(Value0, Value)
+	).
 validate_step(number, Value0, Value) :-
 	number_string(Value, Value0).
 validate_step(integer, Value0, Value) :-
@@ -167,8 +198,9 @@ validate_step(integer, Value0, Value) :-
 validate_step(float, Value0, Value) :-
 	number_string(Value1, Value0),
 	Value is float(Value1).
-validate_step(oneof(List), Value, Value) :-
-	memberchk(Value, List).
+validate_step(oneof(List), Value0, Value) :-
+	member(Value, List),
+	string_value(Value0, Value), !.
 validate_step(password, Value, Value) :-
 	string_length(Value, Len),
 	Len >= 6.
@@ -220,6 +252,45 @@ domain_name_char -->
 domain_special(0'-).
 domain_special(0'_).
 
+%!	is_url(?Scheme, +URL) is semidet.
+%
+%	True if URL looks like a URL that satisfies Scheme.
+
+is_url(Scheme, URL) :-
+	(   string(URL)
+	->  true
+	;   atom(URL)
+	),
+	uri_components(URL, Components),
+	valid_url_scheme(Scheme, Components),
+	valid_authority(Components).
+
+valid_url_scheme(SchemeReq, Components) :-
+	uri_data(scheme, Components, Scheme),
+	nonvar(Scheme),
+	is_scheme(SchemeReq, Scheme).
+
+is_scheme(Scheme, Scheme) :- !.
+is_scheme(http, https).
+
+valid_authority(Components) :-
+	uri_data(authority, Components, Authority),
+	nonvar(Authority).
+
+%!	string_value(+String, +Value) is semidet.
+%
+%	True if String can be  considered   the  stringified  version of
+%	Value.
+
+string_value(Value, Value) :- !.
+string_value(String, Value) :-
+	atom(Value),
+	atom_string(Value, String), !.
+string_value(String, Value) :-
+	number(Value),
+	number_string(String, Value1),
+	Value1 =:= Value.
+
 validate_failed(H, _Value0, Field) :-
 	input_error(Field, H).
 
diff --git a/lib/swish/gitty.pl b/lib/swish/gitty.pl
index bf8c29d..9c92790 100644
--- a/lib/swish/gitty.pl
+++ b/lib/swish/gitty.pl
@@ -45,6 +45,7 @@
 	    gitty_hash/2,		% +Store, ?Hash
 
 	    gitty_reserved_meta/1,	% ?Key
+	    is_gitty_hash/1,		% @Term
 
 	    gitty_diff/4,		% +Store, ?Start, +End, -Diff
 
@@ -190,7 +191,8 @@ gitty_update(Store, Name, Data, Meta, CommitRet) :-
 	->  true
 	;   throw(error(gitty(commit_version(Name, OldHead, Meta.previous)), _))
 	),
-	load_plain_commit(Store, OldHead, OldMeta),
+	load_plain_commit(Store, OldHead, OldMeta0),
+	filter_identity(OldMeta0, OldMeta),
 	get_time(Now),
 	save_object(Store, Data, blob, Hash),
 	Commit = gitty{}.put(OldMeta)
@@ -208,6 +210,26 @@ gitty_update(Store, Name, Data, Meta, CommitRet) :-
 	      ( delete_object(Store, CommitHash),
 		throw(E))).
 
+%!	filter_identity(+Meta0, -Meta)
+%
+%	Remove identification information  from   the  previous  commit.
+%
+%	@tbd: the identity properties should not be hardcoded here.
+
+filter_identity(Meta0, Meta) :-
+	delete_keys([ author,user,avatar,identity,peer,
+		      external_identity, identity_provider, profile_id,
+		      commit_message
+		    ], Meta0, Meta).
+
+delete_keys([], Dict, Dict).
+delete_keys([H|T], Dict0, Dict) :-
+	del_dict(H, Dict0, _, Dict1), !,
+	delete_keys(T, Dict1, Dict).
+delete_keys([_|T], Dict0, Dict) :-
+	delete_keys(T, Dict0, Dict).
+
+
 %%	gitty_update_head(+Store, +Name, +OldCommit, +NewCommit) is det.
 %
 %	Update the head of a gitty  store   for  Name.  OldCommit is the
@@ -401,6 +423,21 @@ gitty_reserved_meta(time).
 gitty_reserved_meta(data).
 gitty_reserved_meta(previous).
 
+
+%%	is_gitty_hash(@Term) is semidet.
+%
+%	True if Term is a possible gitty (SHA1) hash
+
+is_gitty_hash(SHA1) :-
+	atom(SHA1),
+	atom_length(SHA1, 40),
+	atom_codes(SHA1, Codes),
+	maplist(hex_digit, Codes).
+
+hex_digit(C) :- between(0'0, 0'9, C), !.
+hex_digit(C) :- between(0'a, 0'f, C).
+
+
 		 /*******************************
 		 *	    FSCK SUPPORT	*
 		 *******************************/
diff --git a/lib/swish/gitty_driver_files.pl b/lib/swish/gitty_driver_files.pl
index 8517839..eac1d6d 100644
--- a/lib/swish/gitty_driver_files.pl
+++ b/lib/swish/gitty_driver_files.pl
@@ -52,6 +52,7 @@
 :- use_module(library(filesex)).
 :- use_module(library(lists)).
 :- use_module(library(apply)).
+:- use_module(library(error)).
 :- use_module(library(dcg/basics)).
 
 /** <module> Gitty plain files driver
@@ -75,11 +76,13 @@ to rounding the small objects to disk allocation units.
 :- dynamic
 	head/3,				% Store, Name, Hash
 	store/2,			% Store, Updated
+	commit/3,			% Store, Hash, Meta
 	heads_input_stream_cache/2.	% Store, Stream
 :- volatile
 	head/3,
 	store/2,
-	heads_input_stream_cache/2.	% Store, Stream
+	commit/3,
+	heads_input_stream_cache/2.
 
 % enable/disable syncing remote servers running on  the same file store.
 % This facility requires shared access to files and thus doesn't work on
@@ -117,9 +120,15 @@ gitty_file(Store, Head, Hash) :-
 %
 %	Load the commit data as a dict.
 
+load_plain_commit(Store, Hash, Meta) :-
+	must_be(atom, Store),
+	must_be(atom, Hash),
+	commit(Store, Hash, Meta), !.
 load_plain_commit(Store, Hash, Meta) :-
 	load_object(Store, Hash, String, _, _),
-	term_string(Meta, String, []).
+	term_string(Meta0, String, []),
+	assertz(commit(Store, Hash, Meta0)),
+	Meta = Meta0.
 
 %%	store_object(+Store, +Hash, +Header:string, +Data:string) is det.
 %
@@ -191,10 +200,7 @@ gitty_rescan(Store) :-
 
 gitty_scan(Store) :-
 	store(Store, _), !,
-	(   remote_sync(true)
-	->  with_mutex(gitty, remote_updates(Store))
-	;   true
-	).
+	remote_updates(Store).
 gitty_scan(Store) :-
 	with_mutex(gitty, gitty_scan_sync(Store)).
 
@@ -327,7 +333,35 @@ gitty_update_head_sync2(Store, Name, OldCommit, NewCommit) :-
 	    )
 	).
 
+%!	remote_updates(+Store)
+%
+%	Watch for remote updates to the store. We only do this if we did
+%	not do so the last second.
+
+:- dynamic
+	last_remote_sync/2.
+
+remote_updates(_) :-
+	remote_sync(false), !.
+remote_updates(Store) :-
+	remote_up_to_data(Store), !.
 remote_updates(Store) :-
+	with_mutex(gitty, remote_updates_sync(Store)).
+
+remote_updates_sync(Store) :-
+	remote_up_to_data(Store), !.
+remote_updates_sync(Store) :-
+	retractall(last_remote_sync(Store, _)),
+	get_time(Now),
+	asserta(last_remote_sync(Store, Now)),
+	remote_update(Store).
+
+remote_up_to_data(Store) :-
+	last_remote_sync(Store, Last),
+	get_time(Now),
+	Now-Last < 1.
+
+remote_update(Store) :-
 	remote_updates(Store, List),
 	maplist(update_head(Store), List).
 
diff --git a/lib/swish/help.pl b/lib/swish/help.pl
index aec01e6..02416e6 100644
--- a/lib/swish/help.pl
+++ b/lib/swish/help.pl
@@ -3,7 +3,7 @@
     Author:        Jan Wielemaker
     E-mail:        J.Wielemaker@vu.nl
     WWW:           http://www.swi-prolog.org
-    Copyright (c)  2014, VU University Amsterdam
+    Copyright (c)  2014-2017, VU University Amsterdam
     All rights reserved.
 
     Redistribution and use in source and binary forms, with or without
@@ -33,18 +33,76 @@
 */
 
 :- module(swish_help, []).
+:- use_module(library(lists)).
 :- use_module(library(http/http_dispatch)).
 :- use_module(library(http/http_server_files)).
+:- use_module(library(http/http_json)).
+:- use_module(library(http/json)).
 
 /** <module> SWISH help system
 
 This module serves help information for SWISH.
 
-@tbd	Server SWI-Prolog Markdown files.
+@tbd	Serve SWI-Prolog Markdown files.
 */
 
 :- http_handler(swish(help), serve_files_in_directory(swish_help),
 		[id(help),prefix]).
+:- http_handler(swish(help_index),
+		help_index, [id(swish_help_index)]).
 
 user:file_search_path(swish_help, swish(web/help)).
 
+%%	help_index(+Request)
+%
+%       Get a list of registered help  topics. Help topics are described
+%       in a file swish_help('index.json').
+
+help_index(_Request) :-
+	help_files(HelpIndex),
+	reply_json(HelpIndex).
+
+%%	help_files(JSON:list) is det.
+%
+%       JSON is a list of JSON dicts containing the keys below. The list
+%       is  composed  from  all  *.html  files    in   the  search  path
+%       `swish_help`.
+%
+%	  - file:File
+%	  - title:String
+
+help_files(AllExamples) :-
+	findall(Index,
+		absolute_file_name(swish_help(.), Index,
+				   [ access(read),
+				     file_type(directory),
+				     file_errors(fail),
+				     solutions(all)
+				   ]),
+		ExDirs),
+	maplist(index_json, ExDirs, JSON),
+	append(JSON, AllExamples).
+
+index_json(Dir, JSON) :-
+	directory_file_path(Dir, 'index.json', File),
+	access_file(File, read), !,
+	read_file_to_json(File, JSON).
+index_json(Dir, JSON) :-
+	string_concat(Dir, "/*.{html}", Pattern),
+	expand_file_name(Pattern, Files),
+	maplist(help_file_json, Files, JSON).
+
+read_file_to_json(File, JSON) :-
+	setup_call_cleanup(
+	    open(File, read, In, [encoding(utf8)]),
+	    json_read_dict(In, JSON),
+	    close(In)).
+
+%%	help_file_json(+Path, -JSON) is det.
+%
+%	@tbd	Beautify title from file-name (_ --> space, start
+%		with capital, etc).
+
+help_file_json(Path, json{file:File, title:Base}) :-
+	file_base_name(Path, File),
+	file_name_extension(Base, _, File).
diff --git a/lib/swish/highlight.pl b/lib/swish/highlight.pl
index 4fcbe68..38f3f94 100644
--- a/lib/swish/highlight.pl
+++ b/lib/swish/highlight.pl
@@ -48,6 +48,7 @@
 :- use_module(library(prolog_xref)).
 :- use_module(library(memfile)).
 :- use_module(library(prolog_colour)).
+:- use_module(library(lazy_lists)).
 :- if(exists_source(library(helpidx))).
 :- use_module(library(helpidx), [predicate/5]).
 :- endif.
@@ -209,6 +210,7 @@ create_editor(UUID, Editor, Change) :-
 create_editor(UUID, Editor, _Change) :-
 	fetch_editor(UUID, Editor).
 
+% editor and lock are left to symbol-GC if this fails.
 register_editor(UUID, Editor, Role, Lock, Now) :-
 	\+ current_editor(UUID, _, _, _, _),
 	mutex_lock(Lock),
@@ -337,20 +339,25 @@ release_editor(UUID) :-
 check_unlocked :-
 	check_unlocked(unknown).
 
+%!	check_unlocked(+Reason)
+%
+%	Verify that all editors locked by this thread are unlocked
+%	again.
+
 check_unlocked(Reason) :-
 	thread_self(Me),
 	current_editor(_UUID, _TB, _Role, Lock, _),
 	mutex_property(Lock, status(locked(Me, _Count))), !,
+	unlock(Me, Lock),
 	print_message(error, locked(Reason, Me)),
 	assertion(fail).
 check_unlocked(_).
 
-unlocked_editor(UUID) :-
-	thread_self(Me),
-	current_editor(UUID, _TB, _Role, Lock, _),
+unlock(Me, Lock) :-
 	mutex_property(Lock, status(locked(Me, _Count))), !,
-	fail.
-unlocked_editor(_).
+	mutex_unlock(Lock),
+	unlock(Me, Lock).
+unlock(_, _).
 
 %%	update_access(+UUID)
 %
@@ -423,9 +430,9 @@ codemirror_leave_(Request) :-
 %	Mark that our cross-reference data might be obsolete
 
 mark_changed(MemFile, Changed) :-
-	(   Changed == true
-	->  current_editor(UUID, MemFile, _Role, _, _),
-	    retractall(xref_upto_data(UUID))
+	(   Changed == true,
+	    current_editor(UUID, MemFile, _Role, _, _)
+	->  retractall(xref_upto_data(UUID))
 	;   true
 	).
 
@@ -571,23 +578,11 @@ string_source_id(String, SourceID) :-
 
 shadow_editor(Data, TB) :-
 	atom_string(UUID, Data.get(uuid)),
-	fetch_editor(UUID, TB), !,
-	(   Text = Data.get(text)
-	->  size_memory_file(TB, Size),
-	    delete_memory_file(TB, 0, Size),
-	    insert_memory_file(TB, 0, Text),
-	    mark_changed(TB, true)
-	;   Changes = Data.get(changes)
-	->  (   debug(cm(change), 'Patch editor for ~p', [UUID]),
-		catch(maplist(apply_change(TB, Changed), Changes), E,
-		      (release_editor(UUID), throw(E)))
-	    ->	true
-	    ;	release_editor(UUID),
-		assertion(unlocked_editor(UUID)),
-		throw(cm(out_of_sync))
-	    ),
-	    mark_changed(TB, Changed)
-	).
+	setup_call_catcher_cleanup(
+	    fetch_editor(UUID, TB),
+	    once(update_editor(Data, UUID, TB)),
+	    Catcher,
+	    cleanup_update(Catcher, UUID)), !.
 shadow_editor(Data, TB) :-
 	Text = Data.get(text), !,
 	atom_string(UUID, Data.uuid),
@@ -602,6 +597,25 @@ shadow_editor(Data, TB) :-
 shadow_editor(_Data, _TB) :-
 	throw(cm(existence_error)).
 
+update_editor(Data, _UUID, TB) :-
+	Text = Data.get(text), !,
+	size_memory_file(TB, Size),
+	delete_memory_file(TB, 0, Size),
+	insert_memory_file(TB, 0, Text),
+	mark_changed(TB, true).
+update_editor(Data, UUID, TB) :-
+	Changes = Data.get(changes), !,
+	(   debug(cm(change), 'Patch editor for ~p', [UUID]),
+	    maplist(apply_change(TB, Changed), Changes)
+	->  true
+	;   throw(cm(out_of_sync))
+	),
+	mark_changed(TB, Changed).
+
+cleanup_update(exit, _) :- !.
+cleanup_update(_, UUID) :-
+	release_editor(UUID).
+
 :- thread_local
 	token/3.
 
@@ -1040,7 +1054,8 @@ token_info(Token) -->
 	{ _{type:Type, text:Name, arity:Arity} :< Token,
 	  goal_type(_, Type, _), !,
 	  ignore(token_predicate_module(Token, Module)),
-	  predicate_info(Module:Name/Arity, Info)
+	  text_arity_pi(Name, Arity, PI),
+	  predicate_info(Module:PI, Info)
 	},
 	pred_info(Info).
 
@@ -1057,7 +1072,6 @@ pred_tags(Info) -->
 pred_summary(Info) -->
 	html(span(class('pred-summary'), Info.get(summary))).
 
-
 %%	token_predicate_module(+Token, -Module) is semidet.
 %
 %	Try to extract the module from the token.
@@ -1065,6 +1079,11 @@ pred_summary(Info) -->
 token_predicate_module(Token, Module) :-
 	source_file_property(Token.get(file), module(Module)), !.
 
+text_arity_pi('[', 2, consult/1) :- !.
+text_arity_pi(']', 2, consult/1) :- !.
+text_arity_pi(Name, Arity, Name/Arity).
+
+
 %%	predicate_info(+PI, -Info:list(dict)) is det.
 %
 %	Info is a list of dicts providing details about predicates that
diff --git a/lib/swish/include.pl b/lib/swish/include.pl
index 003e66b..c4eab89 100644
--- a/lib/swish/include.pl
+++ b/lib/swish/include.pl
@@ -3,7 +3,7 @@
     Author:        Jan Wielemaker
     E-mail:        J.Wielemaker@vu.nl
     WWW:           http://www.swi-prolog.org
-    Copyright (c)  2015-2016, VU University Amsterdam
+    Copyright (c)  2015-2017, VU University Amsterdam
     All rights reserved.
 
     Redistribution and use in source and binary forms, with or without
@@ -33,12 +33,16 @@
 */
 
 :- module(swish_include,
-	  [
-	  ]).
-:- use_module(gitty).
+          [
+          ]).
+:- use_module(storage).
+:- use_module(config).
 :- use_module(library(sandbox), []).
 :- use_module(library(debug)).
 :- use_module(library(settings)).
+:- use_module(library(filesex)).
+:- use_module(library(error)).
+:- use_module(library(readutil)).
 
 /** <module> Support :- include(File) from SWISH
 
@@ -56,122 +60,201 @@ We allow for hierarchical and circular includes.
 
 
 swish:term_expansion(:- include(FileIn), Expansion) :-
-	atomic(FileIn),
-	atom_string(File, FileIn),
-	(   prolog_load_context(module, Module),
-	    clause(Module:'swish included'(File), true)
-	->  Expansion = []
-	;   Expansion = [ (:- discontiguous('swish included'/1)),
-		          'swish included'(File),
-		          (:- include(stream(Id, Stream, [close(true)])))
-			],
-	    '$push_input_context'(swish_include),
-	    setting(web_storage:directory, Store),
-	    add_extension(File, FileExt),
-	    catch(gitty_data(Store, FileExt, Data, _Meta), _, fail),
-	    atom_concat('swish://', FileExt, Id),
-	    open_string(Data, Stream),
-	    '$pop_input_context'
-	).
+    include_file_id(FileIn, File),
+    (   prolog_load_context(module, Module),
+        clause(Module:'swish included'(File), true)
+    ->  Expansion = []
+    ;   Expansion = [ (:- discontiguous('swish included'/1)),
+                      'swish included'(File),
+                      (:- include(stream(URI, Stream, [close(true)])))
+                    ],
+        '$push_input_context'(swish_include),
+        include_data(File, URI, Data),
+        open_string(Data, Stream),
+        '$pop_input_context'
+    ).
+
+%!  include_data(+FileSpec, -URI, -Data)
+%
+%   Fetch the data to be included and obtain the URI for it.
+
+include_data(Name, URI, Data) :-        % Deal with gitty files
+    atom(Name),
+    !,
+    add_extension(Name, FileExt),
+    catch(storage_file(FileExt, Data, _Meta),
+          error(existence_error(_,_),_),
+          fail),
+    atom_concat('swish://', FileExt, URI).
+include_data(Spec, URI, Data) :-
+    absolute_file_name(Spec, Path, [ file_type(prolog), access(read) ]),
+    read_file_to_string(Path, Data, []),
+    Spec =.. [Alias,_],
+    file_base_name(Path, NameExt),
+    format(atom(URI), 'swish://~w/~w', [Alias, NameExt]).
+
+
+%!  include_file_id(+FileIn, -File) is det.
+%
+%   Normalise an include file identifier and verify its safeness.
+
+include_file_id(FileIn, File) :-
+    atomic(FileIn),
+    !,
+    atom_string(File, FileIn).
+include_file_id(FileIn, File) :-
+    compound(FileIn),
+    FileIn =.. [Alias,NameIn],
+    atom_string(Name, NameIn),
+    (   safe_name(Name),
+        swish_config(include_alias, Alias)
+    ->  true
+    ;   permission_error(include, file, Name)
+    ),
+    File =.. [Alias,Name].
+
+safe_name(Name) :-
+    \+ (   sub_atom(Name, 0, _, _, '../')
+       ;   sub_atom(Name, _, _, _, '/../')
+       ;   sub_atom(Name, _, _, 0, '/..')
+       ;   Name == '..'
+       ).
+
+%!  file_alias(+File, -Spec) is semidet.
+%
+%   Translate Alias/Name into Alias(Name) if Alias  is known and Name is
+%   safe.
+
+file_alias(File, Spec) :-
+    atomic_list_concat([Alias,Name], /, File),
+    swish_config(include_alias, Alias),
+    safe_name(Name),
+    !,
+    Spec =.. [Alias,Name].
+
+%!  add_extension(+File, -FileExt) is det.
+%
+%   Add a file name extension to indicate this is a Prolog file.
 
 add_extension(File, FileExt) :-
-	file_name_extension(_, Ext, File),
-	Ext \== '', !,
-	FileExt = File.
+    file_name_extension(_, Ext, File),
+    Ext \== '',
+    !,
+    FileExt = File.
 add_extension(Hash, Hash) :-
-	is_hash(Hash), !.
+    is_hash(Hash),
+    !.
 add_extension(File, FileExt) :-
-	file_name_extension(File, pl, FileExt).
+    file_name_extension(File, pl, FileExt).
 
 is_hash(Name) :-
-	atom_length(Name, 40),
-	split_string(Name, ":", "0123456789abcdef", [""]).
+    atom_length(Name, 40),
+    split_string(Name, ":", "0123456789abcdef", [""]).
 
 
-		 /*******************************
-		 *	      SANDBOX		*
-		 *******************************/
+                 /*******************************
+                 *            SANDBOX           *
+                 *******************************/
 
 :- multifile
-	sandbox:safe_directive/1.
+    sandbox:safe_directive/1.
 
 sandbox:safe_directive(M:include(stream(Id, Stream, [close(true)]))) :-
-	is_stream(Stream),
-	sub_atom(Id, 0, _, _, 'swish://'),
-	prolog_load_context(module, M).
+    is_stream(Stream),
+    sub_atom(Id, 0, _, _, 'swish://'),
+    prolog_load_context(module, M).
 
 
-		 /*******************************
-		 *	      COLOUR		*
-		 *******************************/
+                 /*******************************
+                 *            COLOUR            *
+                 *******************************/
 
 :- multifile
-	prolog_colour:term_colours/2.
-
-prolog_colour:term_colours((:- include(File)),
-			   neck(directive) -
-			   [ goal(built_in,include(File)) -
-			     [ FileClass
-			     ]
-			   ]) :-
-	debug(include, 'Classifying ~p', [File]),
-	(   atomic(File),
-	    setting(web_storage:directory, Store),
-	    add_extension(File, FileExt),
-	    catch(gitty_commit(Store, FileExt, _Meta), _, fail)
-	->  atom_concat('swish://', FileExt, Id),
-	    FileClass = file(Id)
-	;   FileClass = nofile
-	),
-	debug(include, 'Class ~p', [FileClass]).
-
-
-		 /*******************************
-		 *	      XREF		*
-		 *******************************/
+    prolog_colour:term_colours/2.
+
+prolog_colour:term_colours((:- include(FileIn)),
+                           neck(directive) -
+                           [ goal(built_in,include(FileIn)) -
+                             [ FileClass
+                             ]
+                           ]) :-
+    debug(include, 'Classifying ~p', [FileIn]),
+    (   catch(include_file_id(FileIn, File), _, fail)
+    ->  classify_include(File, FileClass)
+    ;   FileClass = nofile
+    ),
+    debug(include, 'Class ~p', [FileClass]).
+
+classify_include(File, FileClass) :-
+    atom(File),
+    !,
+    add_extension(File, FileExt),
+    catch(storage_meta_data(FileExt, _Meta), _, fail),
+    atom_concat('swish://', FileExt, Id),
+    FileClass = file(Id).
+classify_include(Spec, FileClass) :-
+    absolute_file_name(Spec, Path, [ file_type(prolog), access(read) ]),
+    Spec =.. [Alias,_],
+    file_base_name(Path, NameExt),
+    format(atom(URI), 'swish://~w/~w', [Alias, NameExt]),
+    FileClass = file(URI).
+
+
+                 /*******************************
+                 *            XREF              *
+                 *******************************/
 
 :- multifile
-	prolog:xref_open_source/2,
-	prolog:xref_source_file/3,
-	prolog:xref_source_identifier/2,
-	prolog:xref_source_time/2.
-
-%%	prolog:xref_source_identifier(+Src, -Id) is semidet.
-%%	prolog:xref_open_source(+File, -Stream) is det.
-%%	prolog:xref_source_time(+File, -Modified) is det.
+    prolog:xref_open_source/2,
+    prolog:xref_source_file/3,
+    prolog:xref_source_identifier/2,
+    prolog:xref_source_time/2.
+
+%!  prolog:xref_source_identifier(+Src, -Id) is semidet.
+%!  prolog:xref_open_source(+File, -Stream) is det.
+%!  prolog:xref_source_time(+File, -Modified) is det.
 %
-%	Map swish://file to a file from the gitty store.
+%   Map swish://file to a file from the gitty store.
 
 prolog:xref_source_identifier(Src, Id) :-
-	atom(Src),
-	sub_atom(Src, 0, _, _, 'swish://'), !,
-	Id = Src.
+    atom(Src),
+    sub_atom(Src, 0, _, _, 'swish://'),
+    !,
+    Id = Src.
 
 prolog:xref_open_source(File, Stream) :-
-	atom(File),
-	atom_concat('swish://', Name, File),
-	setting(web_storage:directory, Store),
-	catch(gitty_data(Store, Name, Data, _Meta), _, fail),
-	open_string(Data, Stream).
+    atom(File),
+    atom_concat('swish://', Name, File),
+    (   file_alias(File, Spec)
+    ->  absolute_file_name(Spec, Path, [ file_type(prolog), access(read) ]),
+        open(Path, read, Stream)
+    ;   catch(storage_file(Name, Data, _Meta), _, fail),
+        open_string(Data, Stream)
+    ).
 
 prolog:xref_source_time(File, Modified) :-
-	atom(File),
-	atom_concat('swish://', Name, File),
-	setting(web_storage:directory, Store),
-	catch(gitty_commit(Store, Name, Meta), _, fail),
-	Modified = Meta.get(time).
-
-%%	prolog:xref_source_file(+Term, -Path, +Options)
+    atom(File),
+    atom_concat('swish://', Name, File),
+    (   file_alias(File, Spec)
+    ->  absolute_file_name(Spec, Path, [ file_type(prolog), access(read) ]),
+        time_file(Path, Modified)
+    ;   catch(storage_meta_data(Name, Meta), _, fail),
+        Modified = Meta.get(time)
+    ).
+
+%!  prolog:xref_source_file(+Term, -Path, +Options)
 %
-%	Deal with the above expansion for :- include(program) to support
-%	the cross-referencer.
+%   Deal with the above expansion for :- include(program) to support
+%   the cross-referencer.
 
 prolog:xref_source_file(stream(Id, _Stream, [close(true)]), Id, _).
 prolog:xref_source_file(File, Id, Options) :-
-	atom(File),
-	option(relative_to(Src), Options),
-	atom(Src),
-	sub_atom(Src, 0, _, _, 'swish://'),
-	add_extension(File, FileExt),
-	atom_concat('swish://', FileExt, Id).
+    atom(File),
+    option(relative_to(Src), Options),
+    atom(Src),
+    atom_concat('swish://', SrcFile, Src),
+    add_extension(File, FileExt),
+    file_directory_name(SrcFile, SrcDir),
+    directory_file_path(SrcDir, FileExt, TargetFile),
+    atom_concat('swish://', TargetFile, Id).
 
diff --git a/lib/swish/messages.pl b/lib/swish/messages.pl
new file mode 100644
index 0000000..42ab2fc
--- /dev/null
+++ b/lib/swish/messages.pl
@@ -0,0 +1,47 @@
+/*  Part of SWISH
+
+    Author:        Jan Wielemaker
+    E-mail:        J.Wielemaker@cs.vu.nl
+    WWW:           http://www.swi-prolog.org
+    Copyright (C): 2017, VU University Amsterdam
+			 CWI Amsterdam
+    All rights reserved.
+
+    Redistribution and use in source and binary forms, with or without
+    modification, are permitted provided that the following conditions
+    are met:
+
+    1. Redistributions of source code must retain the above copyright
+       notice, this list of conditions and the following disclaimer.
+
+    2. Redistributions in binary form must reproduce the above copyright
+       notice, this list of conditions and the following disclaimer in
+       the documentation and/or other materials provided with the
+       distribution.
+
+    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
+    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
+    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
+    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
+    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
+    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
+    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
+    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
+    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
+    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
+    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
+    POSSIBILITY OF SUCH DAMAGE.
+*/
+
+:- module(swish_messages, []).
+
+:- multifile
+    prolog:message//1.
+
+prolog:message(swish(Msg)) -->
+    swish_message(Msg).
+
+swish_message(created_data_dir(Dir)) -->
+    [ 'Created data directory "~w"'-[Dir] ].
+swish_message(no_data_dir) -->
+    [ 'Could not find or create a directory for storing data'-[] ].
diff --git a/lib/swish/noble_avatar.pl b/lib/swish/noble_avatar.pl
new file mode 100644
index 0000000..8753172
--- /dev/null
+++ b/lib/swish/noble_avatar.pl
@@ -0,0 +1,275 @@
+/*  Part of SWISH
+
+    Author:        Jan Wielemaker
+    E-mail:        J.Wielemaker@cs.vu.nl
+    WWW:           http://www.swi-prolog.org
+    Copyright (C): 2016, VU University Amsterdam
+			 CWI Amsterdam
+    All rights reserved.
+
+    Redistribution and use in source and binary forms, with or without
+    modification, are permitted provided that the following conditions
+    are met:
+
+    1. Redistributions of source code must retain the above copyright
+       notice, this list of conditions and the following disclaimer.
+
+    2. Redistributions in binary form must reproduce the above copyright
+       notice, this list of conditions and the following disclaimer in
+       the documentation and/or other materials provided with the
+       distribution.
+
+    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
+    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
+    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
+    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
+    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
+    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
+    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
+    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
+    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
+    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
+    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
+    POSSIBILITY OF SUCH DAMAGE.
+*/
+
+:- module(noble_avatar,
+	  [ noble_avatar/2,			% ?Gender, -File
+	    noble_avatar/3,			% ?Gender, -File, ?New
+	    create_avatar/2,			% +PNG, -File
+
+	    existing_noble_avatar/2		% -Gender, -File
+	  ]).
+:- use_module(library(apply)).
+:- use_module(library(lists)).
+:- use_module(library(random)).
+:- use_module(library(filesex)).
+:- use_module(library(process)).
+
+/** <module> Noble Avatar generator
+
+This library generates random avatar images   from  components. The file
+locations of the library are  defined   by  file_search_path/2 rules for
+`noble_avatar_components` (the components) and   `noble_avatar`  for the
+generated avatars.
+
+The probalities for the various components are specified in part/1.
+
+
+## Credits and license
+
+The component images can  be  downloaded   from  the  address below. The
+images are licensed under CC-BY-3.0.  If you use this library with these
+images, please include the following acknowledgements:
+
+  1. Credit Noble Master Games as follows (linking is optional):
+     "Avatar graphics created by Noble Master Games" and link to
+     http://www.noblemaster.com
+  2. Credit the artist "Liea" as follows (optional):
+     "Avatar graphics designed by Mei-Li Nieuwland" and link to
+     http://liea.deviantart.com
+
+@see http://opengameart.org/content/avatar-generator-with-15-trillion-combinations
+*/
+
+
+:- multifile
+	user:file_search_path/2.
+
+user:file_search_path(noble,		       icons(noble)).
+user:file_search_path(noble_avatar_components, noble(components)).
+user:file_search_path(noble_avatar,	       data(avatars)).
+
+:- dynamic
+	noble_dir/1,				% Directory
+	noble/4.				% Part, Gender, I, File
+
+%%	noble_avatar(?Gender, -File) is det.
+%%	noble_avatar(?Gender, -File, ?New) is det.
+%
+%	True when File is the image file  name for a generated avatar of
+%	Gender. If Gender is unspecified, it is generated randomly.
+%
+%	@arg	New is a boolean that indicates whether the avatar is
+%		newly generated (`true`) or we re-generated an existing
+%		one (`false`).  It may be specified as `true` to force
+%		generating a new avatar.  Previously generated avatars
+%		can be queried using existing_noble_avatar/2.
+
+noble_avatar(Gender, Image) :-
+	noble_avatar(Gender, Image, _).
+
+noble_avatar(Gender, Image, New) :-
+	var(New), !,
+	noble_index_components,
+	avatar_components(Gender, IDs, Components),
+	maplist(plus(0'a), IDs, Codes),
+	atom_codes(Base, Codes),
+	file_name_extension(Base, png, PNG),
+	with_mutex(noble_avatar,
+		   create_avatar_sync(Components,
+				      noble_avatar, PNG, Image, New)).
+noble_avatar(Gender, Image, true) :- !,
+	repeat,
+	    noble_avatar(Gender, Image, New),
+	    New == true, !.
+
+%!	create_avatar(+PNG, -Image) is det.
+%
+%	(Re-)create avatar with basename PNG.
+
+create_avatar(PNG, Image) :-
+	file_name_extension(Base, png, PNG),
+	atom_codes(Base, Codes),
+	maplist(plus(0'a), IDs, Codes),
+	noble_index_components,
+	avatar_components(_Gender, IDs, Components),
+	with_mutex(noble_avatar,
+		   create_avatar_sync(Components,
+				      noble_avatar, PNG, Image, _New)).
+
+%%	existing_noble_avatar(-Gender, -Image) is nondet.
+%
+%	True when Image is the image file of a previously generated
+%	avatar of Gender.
+
+existing_noble_avatar(Gender, Image) :-
+	absolute_file_name(noble_avatar(.), Dir,
+			   [ file_type(directory),
+			     solutions(all)
+			   ]),
+	directory_files(Dir, Files),
+	member(Image, Files),
+	file_name_extension(Base, png, Image),
+	sub_atom(Base, 0, 1, _, First),
+	char_code(First, Code),
+	Index is Code-0'a,
+	gender_id(Gender, Index).
+
+
+create_avatar_sync(Components, DirAlias, File, Image, New) :-
+	Location =.. [DirAlias,File],
+	(   absolute_file_name(Location, Image,
+			       [ access(read),
+				 file_errors(fail)
+			       ])
+	->  New = false
+	;   absolute_file_name(Location, Image,
+			       [ access(write), file_errors(fail) ])
+	->  composite(Components, Image),
+	    New	= true
+	;   Dir =.. [DirAlias,.],
+	    absolute_file_name(Dir, DirPath, [solutions(all)]),
+	    file_directory_name(DirPath, Parent),
+	    exists_directory(Parent),
+	    \+ exists_directory(DirPath)
+	->  make_directory(DirPath),
+	    absolute_file_name(Location, Image, [access(write)]),
+	    composite(Components, Image)
+	).
+
+composite(Components, Image) :-
+	noble_dir(Dir),
+	phrase(composite(Components, Dir), Argv, [file(Image)]),
+	process_create(path(convert), Argv, []).
+
+composite([], _) -->
+	[ '-background', 'none', '-flatten' ].
+composite([File|T], Dir) -->
+	{ directory_file_path(Dir, File, AbsFile)
+	},
+	[ '-page', '+0+0', file(AbsFile) ],
+	composite(T, Dir).
+
+avatar_components(Gender, [GID|IDs], Files) :-
+	gender_id(Gender, GID),
+	parts(Parts),
+	files(Parts, Gender, IDs, Files).
+
+files([], _, [], []).
+files([P:H-Gender|T], Gender, [I|IDs], [File|Files]) :-
+	(   var(I), I \== 0
+	->  maybe(P)
+	;   true
+	),
+	file(H, Gender, I, File), !,
+	files(T, Gender, IDs, Files).
+files([_|T], Gender, [0|IDs], Files) :-
+	files(T, Gender, IDs, Files).
+
+file(Part, Gender, I, File) :-
+	findall(I, noble(Part, Gender, I, _), IL),
+	random_member(I, IL),
+	noble(Part, Gender, I, File).
+
+gender_id(Var, ID) :-
+	var(Var), var(ID),
+	ID is 1+random(2),
+	gender_id(Var, ID), !.
+gender_id(male, 1).
+gender_id(female, 2).
+
+
+%%	parts(-Parts:list) is det.
+%
+%	True when Parts is the list  of part specifications for creating
+%	a new avatar. Each specification is a term
+%
+%	    Probability:Part-Gender
+%
+%	Part is included with Probability and only of Gender matches
+%	the target Gender.
+
+parts([ 0.5:pattern - _,
+	1.0:head - _,
+	1.0:mouth - _,
+	1.0:eye - _,
+	0.5:eyepatch - _,
+	0.3:glasses - _,
+	0.3:mustache - male,
+	0.5:beard - male,
+	0.8:hair - _,
+	0.2:accessory - _,
+	0.5:necklace - _,
+	0.3:boa - _,
+	0.2:scar - _,
+	0.1:sideburn - _
+      ]).
+
+%%	noble_index_components
+%
+%	Create an index for the Noble  Avatar components. The components
+%	are searched for in the directory noble_avatar_components(.).
+
+noble_index_components :-
+	noble_dir(_), !.
+noble_index_components :-
+	with_mutex(noble_avatar, noble_index_components_sync).
+
+noble_index_components_sync :-
+	noble_dir(_), !.
+noble_index_components_sync :-
+	retractall(noble_dir(_)),
+	retractall(noble(_,_,_,_)),
+	absolute_file_name(noble_avatar_components(.), Dir,
+			   [ file_type(directory)
+			   ]),
+	directory_files(Dir, Files),
+	maplist(noble_file, Files),
+	assertz(noble_dir(Dir)).
+
+noble_file(File) :-
+	file_name_extension(Base, png, File),
+	atomic_list_concat([avatar,Part,V], '_', Base),
+	(   atom_concat(f, NA, V),
+	    atom_number(NA, N)
+	->  Gender = female
+	;   atom_concat(m, NA, V),
+	    atom_number(NA, N)
+	->  Gender = male
+	;   atom_number(V, N)
+	), !,
+	assert(noble(Part, Gender, N, File)).
+noble_file(_).
+
+
diff --git a/lib/swish/pack/profile/pack.pl b/lib/swish/pack/profile/pack.pl
new file mode 100644
index 0000000..84b9858
--- /dev/null
+++ b/lib/swish/pack/profile/pack.pl
@@ -0,0 +1,7 @@
+name(profile).
+version('0.1.0').
+title('Manage user profiles').
+keywords([user, profile, http]).
+author( 'Jan Wielemaker', 'jan@swi-prolog.org' ).
+home('https://github.com/JanWielemaker/profile' ).
+download( 'https://github.com/JanWielemaker/profile/releases/*.zip' ).
diff --git a/lib/swish/pack/profile/prolog/profile/backend/profile_prolog.pl b/lib/swish/pack/profile/prolog/profile/backend/profile_prolog.pl
new file mode 100644
index 0000000..aac1ad5
--- /dev/null
+++ b/lib/swish/pack/profile/prolog/profile/backend/profile_prolog.pl
@@ -0,0 +1,200 @@
+/*  Part of SWI-Prolog
+
+    Author:        Jan Wielemaker
+    E-mail:        J.Wielemaker@vu.nl
+    WWW:           http://www.swi-prolog.org
+    Copyright (c)  2016-2017, VU University Amsterdam
+    All rights reserved.
+
+    Redistribution and use in source and binary forms, with or without
+    modification, are permitted provided that the following conditions
+    are met:
+
+    1. Redistributions of source code must retain the above copyright
+       notice, this list of conditions and the following disclaimer.
+
+    2. Redistributions in binary form must reproduce the above copyright
+       notice, this list of conditions and the following disclaimer in
+       the documentation and/or other materials provided with the
+       distribution.
+
+    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
+    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
+    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
+    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
+    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
+    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
+    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
+    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
+    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
+    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
+    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
+    POSSIBILITY OF SUCH DAMAGE.
+*/
+
+:- module(impl_profile_prolog, []).
+:- use_module(library(persistency)).
+:- use_module(library(settings)).
+:- use_module(library(option)).
+:- use_module(library(apply)).
+
+/** <module> User Profile backend as pure Prolog
+
+This module is a backend for   user_profile.pl, realising the persistent
+store as a set of Prolog files.  The properties of this profile are:
+
+  - No dependencies and installation.
+  - Scalabe to about 100,000 profiles.  Much larger sets will result
+    in prohibitively long server startup time and memory usage.
+  - Profiles can only be modified on one server.  Databases may
+    be distributed and used on different servers.
+*/
+
+:- setting(user_profile:profile_db, callable, data(profiles),
+	   "File holding profiles").
+:- setting(user_profile:session_db, callable, data(sessions),
+	   "File holding active sessions").
+
+:- persistent
+	impl_profile_prolog_profile:
+	(   profile(profile_id:atom),
+	    profile_attribute(profile_id:atom, name:atom, value)
+	),
+	impl_profile_prolog_session:
+	(   session(profile_id:atom, session_id:atom, timeout:number)
+	).
+
+:- public
+	impl_profile_open_db/1,
+	impl_profile_create/2,
+	impl_current_profile/1,
+	impl_current_profile/2,
+	impl_profile_property/2,
+	impl_set_profile/3,
+	impl_profile_remove/1,
+	impl_profile_remove/2,
+	impl_profile_add_session/3,
+	impl_profile_refresh_session/2,
+	impl_profile_remove_session/2,
+	impl_profile_session/2.
+
+%%	impl_profile_open_db(+Options)
+
+impl_profile_open_db(Options) :-
+	setting(user_profile:profile_db, ProfileDBSpec),
+	setting(user_profile:session_db, SessionDBSpec),
+	db_file(ProfileDBSpec, ProfileDB),
+	db_file(SessionDBSpec, SessionDB),
+	db_attach(impl_profile_prolog_profile:ProfileDB, Options),
+	db_attach(impl_profile_prolog_session:SessionDB, Options).
+
+db_file(Spec, File) :-
+	absolute_file_name(Spec, File,
+			   [ extensions([db]),
+			     access(write)
+			   ]).
+
+
+%%	impl_profile_create(+ProfileID, +CanAttributes)
+
+impl_profile_create(ProfileID, CanAttributes) :-
+	impl_profile_prolog_profile:assert_profile(ProfileID),
+	maplist(impl_set_profile(ProfileID), CanAttributes).
+
+%%	impl_current_profile(?ProfileID)
+
+impl_current_profile(ProfileID) :-
+	impl_profile_prolog_profile:profile(ProfileID).
+
+%%	impl_current_profile(?ProfileID, ?Attributes)
+
+impl_current_profile(ProfileID, Attributes) :-
+	impl_current_profile(ProfileID),
+	findall(Name-Value,
+		impl_profile_prolog_profile:
+		    profile_attribute(ProfileID, Name, Value),
+		Pairs),
+	dict_pairs(Attributes, user_profile, Pairs).
+
+%%	impl_profile_property(?ProfileID, ?Attribute)
+
+impl_profile_property(ProfileID, Attribute) :-
+	callable(Attribute), !,
+	Attribute =.. [Name,Value],
+	impl_profile_prolog_profile:
+	    profile_attribute(ProfileID, Name, Value).
+impl_profile_property(ProfileID, Attribute) :-
+	impl_profile_prolog_profile:
+	    profile_attribute(ProfileID, Name, Value),
+	Attribute =.. [Name,Value].
+
+%%	impl_set_profile(+ProfileID, +CanAttribute, -Modified)
+
+impl_set_profile(ProfileID, CanAttribute) :-
+	impl_set_profile(ProfileID, CanAttribute, _).
+impl_set_profile(ProfileID, CanAttribute, Modified) :-
+	CanAttribute =.. [Name,Value],
+	(   impl_profile_prolog_profile:
+		profile_attribute(ProfileID, Name, Value)
+	->  Modified = false
+	;   impl_profile_prolog_profile:
+	        retractall_profile_attribute(ProfileID, Name, _),
+	    impl_profile_prolog_profile:
+	        assert_profile_attribute(ProfileID, Name, Value),
+	    Modified = true
+	).
+
+%%	impl_profile_remove(+ProfileID)
+
+impl_profile_remove(ProfileID) :-
+	impl_profile_prolog_profile:
+	    retractall_profile(ProfileID),
+	impl_profile_prolog_profile:
+	    retractall_profile_attribute(ProfileID, _, _).
+
+%%	impl_profile_remove(+ProfileID, +Attribute)
+
+impl_profile_remove(ProfileID, Attribute) :-
+	impl_profile_prolog_profile:
+	    retractall_profile_attribute(ProfileID, Attribute, _).
+
+
+		 /*******************************
+		 *	      SESSIONS		*
+		 *******************************/
+
+:- dynamic
+	tmp_session/3,			% ProfileID, SessionID, DeadLine
+	session_last_usage/2.		% SessionID, Time
+
+%%	impl_profile_add_session(+ProfileID, +SessionID, +Options)
+
+impl_profile_add_session(ProfileID, SessionID, Options) :-
+	option(timeout(Timeout), Options),
+	get_time(Now),
+	Deadline is Now+Timeout,
+	impl_profile_prolog_session:
+	    assert_session(ProfileID, SessionID, Deadline).
+
+%%	impl_profile_refresh_session(+ProfileID, +SessionID)
+
+impl_profile_refresh_session(_ProfileID, _SessionID).
+
+%%	impl_profile_remove_session(+ProfileID, +SessionID)
+
+impl_profile_remove_session(ProfileID, SessionID) :-
+	impl_profile_prolog_session:
+	    retractall_session(ProfileID, SessionID, _).
+
+%%	impl_profile_session(?ProfileID, ?SessionID) is nondet.
+
+impl_profile_session(ProfileID, SessionID) :-
+	get_time(Now),
+	impl_profile_prolog_session:
+	    session(ProfileID, SessionID, Deadline),
+	(   Deadline < Now
+	->  true
+	;   impl_profile_prolog_session:
+		retractall_session(ProfileID, SessionID, _),
+	    fail
+	).
diff --git a/lib/swish/pack/profile/prolog/user_profile.pl b/lib/swish/pack/profile/prolog/user_profile.pl
new file mode 100644
index 0000000..898d409
--- /dev/null
+++ b/lib/swish/pack/profile/prolog/user_profile.pl
@@ -0,0 +1,475 @@
+/*  Part of SWI-Prolog
+
+    Author:        Jan Wielemaker
+    E-mail:        J.Wielemaker@vu.nl
+    WWW:           http://www.swi-prolog.org
+    Copyright (c)  2017, CWI Amsterdam
+    All rights reserved.
+
+    Redistribution and use in source and binary forms, with or without
+    modification, are permitted provided that the following conditions
+    are met:
+
+    1. Redistributions of source code must retain the above copyright
+       notice, this list of conditions and the following disclaimer.
+
+    2. Redistributions in binary form must reproduce the above copyright
+       notice, this list of conditions and the following disclaimer in
+       the documentation and/or other materials provided with the
+       distribution.
+
+    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
+    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
+    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
+    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
+    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
+    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
+    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
+    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
+    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
+    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
+    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
+    POSSIBILITY OF SUCH DAMAGE.
+*/
+
+:- module(user_profile,
+	  [ profile_open_db/1,		% +Options
+
+	    profile_create/2,		% ?ProfileId, +Attributes
+	    current_profile/1,		% ?ProfileId
+	    current_profile/2,		% ?ProfileId, -Attributes
+	    profile_property/2,		% ?ProfileId, ?Attribute
+	    set_profile/2,		% +ProfileId, +Property
+	    set_profile/3,		% +ProfileId, +Property, -Modified
+	    profile_remove/2,		% +ProfileId, +Property
+	    profile_remove/1,		% +ProfileId
+
+	    profile_add_session/3,	% +ProfileId, +SessionID, +Options
+	    profile_remove_session/2,	% +ProfileId, +SessionID
+	    profile_session/2,		% ?ProfileId, ?SessionID
+	    profile_refresh_session/2,	% +ProfileId, +SessionID
+
+	    profile_canonical_value/3	% +Attribute, +Value0, -Value
+	  ]).
+:- use_module(library(uuid)).
+:- use_module(library(error)).
+:- use_module(library(apply)).
+:- use_module(library(option)).
+:- use_module(library(settings)).
+:- use_module(library(uri)).
+:- use_module(library(lists)).
+
+/** <module> User Profile Management
+
+This module implements  user  profile   management,  in  particular  for
+managing authentication and authorization for   HTTP  servers. It mainly
+defines the interface that can be used within an HTTP application.
+
+The  actual  storage  is  left  to    a  plugin  providing  the  backend
+implementation. Backend choices may  depend   on  integration needs with
+other services, scale of the site  (number of users), distribution, ease
+of installation.
+
+The typical setup sequence is
+
+```
+:- use_module(library(http/user_profile)).
+:- use_module(library(http/impl/profile_prolog)).
+:- set_setting(user_profile:backend, impl_profile_prolog).
+
+:- multifile
+	user_profile:attribute/3.
+
+user_profile:attribute_type(name, string, []).
+...
+
+```
+*/
+
+:- multifile
+	attribute/3.			% ?Attribute, ?Type, ?Options
+
+:- setting(backend, atom, user_profile_prolog,
+	   "Backend to use (name of the module").
+:- setting(session_timeout, number, 900,
+	   "Default timeout for session based logins").
+:- setting(session_persistency, boolean, false,
+	   "Default session persistency handling").
+
+
+		 /*******************************
+		 *	      DATABASE		*
+		 *******************************/
+
+%%	profile_open_db(+Options) is det.
+%
+%	Open the profile database. Must  be   called  before  any of the
+%	other  profile  API  predicates.  Options  depend  on  the  used
+%	backend.
+
+profile_open_db(Options) :-
+	setting(backend, Backend),
+	Backend:impl_profile_open_db(Options).
+
+
+		 /*******************************
+		 *	       CREATE		*
+		 *******************************/
+
+%%	profile_create(?ProfileID, +Attributes) is det.
+%
+%	Create a new user profile with the given initial attributes.
+%
+%	@arg	Attributes is a list of Name(Value) terms.
+
+profile_create(ProfileID, Attributes) :-
+	instantiate_profile_id(ProfileID),
+	maplist(typecheck_attribute, Attributes, CanAttributes),
+	(   current_profile(ProfileID)
+	->  permission_error(redefine, user_profile, ProfileID)
+	;   true
+	),
+	setting(backend, Backend),
+	Backend:impl_profile_create(ProfileID, CanAttributes).
+
+instantiate_profile_id(ProfileID) :-
+	var(ProfileID), !,
+	uuid(ProfileID).
+instantiate_profile_id(ProfileID) :-
+	must_be(atom, ProfileID).
+
+typecheck_attribute(Term, Canonical) :-
+	attribute_nv(Term, Name, Value0),
+	profile_canonical_value(Name, Value0, Value),
+	Canonical =.. [Name,Value].
+
+%!	profile_canonical_value(+Attribute, +ValueIn, -Value) is det.
+%
+%	True when Value is  the  canonical   value  for  Attribute  that
+%	satisfies the type constraint for Attribute.
+%
+%	@error type_error(Type, ValueIn) if the type is wrong
+%	@error existence_error(profile_attribute, Attribute) if the
+%	       attribute is unknown.
+
+profile_canonical_value(Name, Value0, Value) :-
+	(   attribute(Name, Type, _)
+	->  must_be(ground, Type),
+	    (   convert_attribute_value(Type, Value0, Value)
+	    ->	true
+	    ;	Value = Value0,
+		must_be(Type, Value)
+	    )
+	;   existence_error(profile_attribute, Name)
+	).
+
+%!	convert_attribute_value(+Type, +Input, -Value)
+%
+%	True when Value is the result of converting Input to Type.
+
+convert_attribute_value(Type, Text, String) :-
+	string_value(Type),
+	text(Text), !,
+	atom_string(Text, String).
+convert_attribute_value(float, Int, Float) :-
+	integer(Int),
+	Float is float(Int).
+convert_attribute_value(string, ip(A,B,C,D), String) :-
+	format(string(String), '~w.~w.~w.~w', [A,B,C,D]).
+convert_attribute_value(oneof(Values), Text, Value) :-
+	member(Value, Values),
+	string_value(Text, Value), !.
+
+string_value(string).
+string_value(url).
+string_value(url(_Scheme)).
+string_value(email).
+
+string_value(Value, Value) :- !.
+string_value(String, Value) :-
+	atom(Value),
+	atom_string(Value, String), !.
+string_value(String, Value) :-
+	number(Value),
+	number_string(String, Value1),
+	Value1 =:= Value.
+
+text(T) :- atom(T), !.
+text(T) :- string(T), !.
+
+attribute_nv(Term, _Name, _Value) :-
+	var(Term), !,
+	instantiation_error(Term).
+attribute_nv(Term, Name, Value) :-
+	compound(Term),
+	compound_name_arguments(Term, Name, [Value]), !.
+attribute_nv(Name = Value, Name, Value) :- !,
+	must_be(atom, Name).
+attribute_nv(Name - Value, Name, Value) :- !,
+	must_be(atom, Name).
+attribute_nv(Term, _Name, _Value) :-
+	type_error(name_value, Term).
+
+
+		 /*******************************
+		 *	       QUERY		*
+		 *******************************/
+
+%%	current_profile(?ProfileID) is nondet.
+%
+%	True when ProfileID is a currently known user profile.
+
+current_profile(ProfileID) :-
+	setting(backend, Backend),
+	Backend:impl_current_profile(ProfileID).
+
+%%	current_profile(?ProfileID, -Attributes:dict) is nondet.
+%
+%	True when ProfileID is a currently   known user profile with the
+%	given attributes.
+
+current_profile(ProfileID, Attributes) :-
+	setting(backend, Backend),
+	Backend:impl_current_profile(ProfileID, Attributes0),
+	add_defaults(Attributes0, Attributes).
+
+add_defaults(Attributes0, Attributes) :-
+	findall(Name-Value, default_attribute(Name, Value), Pairs),
+	Pairs \== [], !,
+	dict_pairs(Defaults, user_profile, Pairs),
+	Attributes = Defaults.put(Attributes0).
+add_defaults(Attributes, Attributes).
+
+default_attribute(Name, Value) :-
+	attribute(Name, _Type, Options),
+	memberchk(default(Value), Options).
+
+
+%%	profile_property(?ProfileID, ?Property:compound) is nondet.
+%
+%	True when the user with ProfileID   has  Property. Property is a
+%	term Name(Value).
+
+profile_property(ProfileID, Property) :-
+	nonvar(ProfileID),
+	nonvar(Property), !,
+	attribute_nv(Property, Name, Value),
+	setting(backend, Backend),
+	(   VarP =.. [Name,Value0],
+	    Backend:impl_profile_property(ProfileID, VarP)
+	->  Value = Value0
+	;   default_attribute(Name, Value)
+	).
+profile_property(ProfileID, Property) :-
+	setting(backend, Backend),
+	Backend:impl_profile_property(ProfileID, Property).
+
+
+		 /*******************************
+		 *	       UPDATE		*
+		 *******************************/
+
+%%	set_profile(+ProfileID, +Attribute) is det.
+%%	set_profile(+ProfileID, +Attribute, -Modified) is det.
+%
+%	Set an attribute of the profile.
+%
+%	@arg Attribute is a term Name(Value)
+%	@arg Modified is unified with a boolean, indicating whether
+%	     or not the value was modified.
+
+set_profile(ProfileID, Attribute) :-
+	set_profile(ProfileID, Attribute, _).
+
+set_profile(ProfileID, Attribute, Modified) :-
+	must_be(atom, ProfileID),
+	typecheck_attribute(Attribute, CanAttribute),
+	setting(backend, Backend),
+	Backend:impl_set_profile(ProfileID, CanAttribute, Modified).
+
+%%	profile_remove(+ProfileID) is det.
+%
+%	Completely destroy a profile.
+
+profile_remove(ProfileID) :-
+	must_be(atom, ProfileID),
+	setting(backend, Backend),
+	Backend:impl_profile_remove(ProfileID).
+
+%%	profile_remove(+ProfileID, +Attribute) is det.
+%
+%	Remove an attribute from a profile.
+
+profile_remove(ProfileID, Attribute) :-
+	must_be(atom, ProfileID),
+	must_be(atom, Attribute),
+	setting(backend, Backend),
+	Backend:impl_profile_remove(ProfileID, Attribute).
+
+
+		 /*******************************
+		 *	SESSION MANAGEMENT	*
+		 *******************************/
+
+%%	profile_add_session(+ProfileID, +SessionID, +Options) is det.
+%
+%	Associate a profile with a session (login). Options defined are:
+%
+%	  - timeout(+Seconds)
+%	  Max idle time for the session.
+%	  - persistent(+Boolean)
+%	  If `true`, store the session association persistently, such
+%	  that a server restart maintains the login.
+
+profile_add_session(ProfileID, SessionID, Options) :-
+	must_be(atom, ProfileID),
+	must_be(atom, SessionID),
+	setting(session_timeout, DefTimeOut),
+	setting(session_persistency, DefPresistency),
+	option(timeout(TimeOut), Options, DefTimeOut),
+	option(persistent(Persistent), Options, DefPresistency),
+	local_add_session(ProfileID, SessionID,
+			  [ timeout(TimeOut),
+			    persistent(Persistent)
+			  ]).
+
+%%	profile_refresh_session(+ProfileID, +SessionID) is det.
+%
+%	Update the last access time for the indicated session.
+
+profile_refresh_session(ProfileID, SessionID) :-
+	must_be(atom, ProfileID),
+	must_be(atom, SessionID),
+	local_refresh_session(ProfileID, SessionID).
+
+%%	profile_remove_session(+ProfileID, +SessionID) is det.
+%
+%	Remove the association of a profile with a session (logout).
+
+profile_remove_session(ProfileID, SessionID) :-
+	must_be(atom, ProfileID),
+	must_be(atom, SessionID),
+	local_remove_session(ProfileID, SessionID).
+
+%%	profile_session(?ProfileID, ?SessionID) is nondet.
+%
+%	True when ProfileID is associated (logged in) with SessionID.
+
+profile_session(ProfileID, SessionID) :-
+	local_session(ProfileID, SessionID).
+
+
+		 /*******************************
+		 *	  LOCAL SESSIONS	*
+		 *******************************/
+
+:- dynamic
+	tmp_session/3,			% ProfileID, SessionID, DeadLine
+	session_last_usage/2.		% SessionID, Time
+:- volatile
+	tmp_session/3,
+	session_last_usage/2.
+
+local_add_session(ProfileID, SessionID, Options) :-
+	option(persistent(false), Options), !,
+	option(timeout(Timeout), Options),
+	get_time(Now),
+	asserta(tmp_session(ProfileID, SessionID, Timeout)),
+	asserta(session_last_usage(SessionID, Now)).
+local_add_session(ProfileID, SessionID, Options) :-
+	setting(backend, Backend),
+	Backend:impl_profile_add_session(ProfileID, SessionID, Options).
+
+local_refresh_session(ProfileID, SessionID) :-
+	tmp_session(ProfileID, SessionID, _Timeout), !,
+	get_time(Now),
+	retractall(session_last_usage(SessionID, _)),
+	asserta(session_last_usage(SessionID, Now)).
+local_refresh_session(ProfileID, SessionID) :-
+	setting(backend, Backend),
+	Backend:impl_profile_refresh_session(ProfileID, SessionID).
+
+local_remove_session(ProfileID, SessionID) :-
+	retract(tmp_session(ProfileID, SessionID, _)), !.
+local_remove_session(ProfileID, SessionID) :-
+	setting(backend, Backend),
+	Backend:impl_profile_remove_session(ProfileID, SessionID).
+
+local_session(ProfileID, SessionID) :-
+	var(ProfileID), var(SessionID), !,
+	(   tmp_session(_, SessionID, _),
+	    local_session(ProfileID, SessionID)
+	;   setting(backend, Backend),
+	    Backend:impl_profile_session(ProfileID, SessionID)
+	).
+local_session(ProfileID, SessionID) :-
+	tmp_session(ProfileID, SessionID, TimeOut), !,
+	session_last_usage(SessionID, LastUsage),
+	get_time(Now),
+	(   LastUsage+TimeOut < Now
+	->  true
+	;   retractall(tmp_session(ProfileID, SessionID, _)),
+	    retractall(session_last_usage(SessionID, _)),
+	    fail
+	).
+local_session(ProfileID, SessionID) :-
+	setting(backend, Backend),
+	Backend:impl_profile_session(ProfileID, SessionID).
+
+
+		 /*******************************
+		 *	      TYPES		*
+		 *******************************/
+
+:- multifile error:has_type/2.
+
+%!	error:has_type(+Type, +Value) is semidet.
+%
+%	True if Value satisfies Type.   This  implementation extends the
+%	type logic defined  in  library(error)   with  some  types  that
+%	commonly apply to user profiles.
+%
+%	@tbd: extend with e.g., zip, country, phone, date
+
+error:has_type(url(http), URI) :-
+	string(URI),
+	uri_components(URI, Components),
+	valid_http_scheme(Components),
+	valid_authority(Components).
+error:has_type(email, Email) :-
+	string(Email),
+	split_string(Email, "@", "", [_,_]).
+error:has_type(time_stamp(_Format), Stamp) :-
+	number(Stamp).
+
+valid_http_scheme(Components) :-
+	uri_data(scheme, Components, Scheme),
+	nonvar(Scheme),
+	http_scheme(Scheme).
+
+http_scheme(http).
+http_scheme(https).
+
+valid_authority(Components) :-
+	uri_data(authority, Components, Authority),
+	nonvar(Authority).
+
+
+		 /*******************************
+		 *	      HOOKS		*
+		 *******************************/
+
+%%	attribute(?Attribute, ?Type, ?Options) is nondet.
+%
+%	Multifile hook that defines that the profile attribute Attribute
+%	must have the type Type. Type are  types as defined by must_be/2
+%	from library(error).  Options defined are:
+%
+%	  - access(+Access)
+%	  Defines whether or not the user can update the attribute
+%	  value. Access is one of `rw` (default) or `ro`.
+%	  - hidden(+Boolean)
+%	  If `true`, the attribute is not displayed in the user
+%	  profile.
+%	  - default(+Value)
+%	  Assumed default if the value is unknown.
diff --git a/lib/swish/pack/smtp/pack.pl b/lib/swish/pack/smtp/pack.pl
new file mode 100644
index 0000000..db2f2bf
--- /dev/null
+++ b/lib/swish/pack/smtp/pack.pl
@@ -0,0 +1,7 @@
+name(smtp).
+title('An (E)SMTP client for sending mail').
+version('1.0.0').
+keywords([smtp, mail, sendmail]).
+author('Jan Wielemaker', 'J.Wielemaker@vu.nl').
+home('https://github.com/JanWielemaker/smtp').
+download('https://github.com/JanWielemaker/smtp/releases/*.zip').
diff --git a/lib/swish/pack/smtp/prolog/smtp.pl b/lib/swish/pack/smtp/prolog/smtp.pl
new file mode 100644
index 0000000..67cf51b
--- /dev/null
+++ b/lib/swish/pack/smtp/prolog/smtp.pl
@@ -0,0 +1,522 @@
+/*  Author:        Jan Wielemaker
+    E-mail:        J.Wielemaker@vu.nl
+    WWW:           http://www.swi-prolog.org
+    Copyright (C): 2012-2017, VU University Amsterdam
+                              CWI Amsterdam
+    All rights reserved.
+
+    Redistribution and use in source and binary forms, with or without
+    modification, are permitted provided that the following conditions
+    are met:
+
+    1. Redistributions of source code must retain the above copyright
+       notice, this list of conditions and the following disclaimer.
+
+    2. Redistributions in binary form must reproduce the above copyright
+       notice, this list of conditions and the following disclaimer in
+       the documentation and/or other materials provided with the
+       distribution.
+
+    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
+    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
+    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
+    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
+    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
+    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
+    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
+    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
+    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
+    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
+    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
+    POSSIBILITY OF SUCH DAMAGE.
+*/
+
+:- module(smtp,
+          [ smtp_send_mail/3            % +To, :Goal, +Options
+          ]).
+:- use_module(library(socket)).
+:- use_module(library(ssl)).
+:- use_module(library(readutil)).
+:- use_module(library(settings)).
+:- use_module(library(option)).
+:- use_module(library(lists)).
+:- use_module(library(debug)).
+:- use_module(library(error)).
+:- use_module(library(dcg/basics)).
+
+:- meta_predicate
+    smtp_send_mail(+, 1, +).
+
+/** <module> Send E-mail through SMTP
+
+This module provides a  simple  means  to   send  E-mail  from  a Prolog
+application.  Here is a simple example:
+
+==
+send_message(Out) :-
+        format(Out, 'Hi Alice,\n\n', []),
+        format(Out, 'Want to go out tonight?\n\n', []),
+        format(Out, '\tCheers, Bob\n', []).
+
+
+?- smtp_send_mail('alice@wonderland.com',
+                  send_message,
+                  [ subject('Tonight'),
+                    from('bob@wonderland.com')
+                  ]).
+
+This library currently supports good old  SMTP, encrypted and authorized
+ESMTP. Both SSL/TLS and STARTTLS  encryption is supported. Authorization
+is supported using =PLAIN= and =LOGIN= methods.
+
+Data is currently being sent using the =DATA= keyword.
+
+@tbd    Support more advanced data transport extensions such as sending
+        MIME messages.
+==
+*/
+
+:- setting(host, atom, localhost,
+           'Name of the SMTP host for relaying the mail').
+:- setting(port, integer, 0,
+           'Port on which the SMTP host listens (0: default)').
+:- setting(security, oneof([none,ssl,tls,starttls]), none,
+           'Security system to use').
+:- setting(from, atom, '',
+           'Default from-address').
+:- setting(user, atom, '',
+           'Default user to authenticate').
+:- setting(password, atom, '',
+           'Default password for smtp:user').
+:- setting(auth_method, oneof([plain,login,default]), default,
+           'Default authorization to use').
+:- setting(hostname, atom, '',
+           'Default hostname').
+
+:- meta_predicate
+    setup_call_error_cleanup(0,0,0).
+
+%!  smtp_send_mail(+To, :Goal, +Options)
+%
+%   Send mail using SMTP.  To is the e-mail address of the receiver.
+%   Options:
+%
+%     * smtp(+Host)
+%       the name or ip address for smtp host, eg. swi-prolog.org
+%     * from(+FromAddress)
+%       atomic identifies sender address.  Provides the default
+%       for header(from(From)).
+%     * date(+Date)
+%       Set the date header.  Default is to use the current time.
+%     * subject(+Subject)
+%       atomic: text for 'Subject:' email header
+%     * auth(User-Password)
+%       authentication credentials, as atoms or strings.
+%     * auth_method(+PlainOrLoginOrNone)
+%       type of authentication. Default is =default=, alternatives
+%       are =plain= and =login=
+%     * security(Security)
+%       one of: `none`, `ssl`, `tls`, `starttls`
+%     * content_type(+ContentType)
+%       sets =|Content-Type|= header
+%     * mailed_by(By)
+%       add X-Mailer: SWI-Prolog <version>, pack(smtp) to header
+%       iff By == true
+%     * header(Name(Val))
+%       add HName: Val to headers. HName is Name if Name's first
+%       letter is a capital, and it is Name after capitalising its
+%       first letter otherwise. For instance header(from('My name,
+%       me@server.org')) adds header "From: My name, my@server.org"
+%       and header('FOO'(bar)) adds "FOO: bar"
+%
+%   Defaults are provided by settings associated to this module.
+%
+%   Listens to debug(smtp) which  for   instance  reports failure to
+%   connect, (computation fails as per non-debug execution).
+%
+%   @arg To is an atom holding the target address
+%   @arg Goal is called as call(Goal, Stream) and must provide
+%        the body of the message.
+
+smtp_send_mail(To, Goal, Options) :-
+    setting(security, DefSecurity),
+    setting(host, DefHost),
+    setting(port, DefPort0),
+    option(security(Security), Options, DefSecurity),
+    default_port(Security, DefPort0, DefPort),
+    option(smtp(Host), Options, DefHost),
+    option(port(Port), Options, DefPort),
+    hostname(HostName, Options),
+    DefOptions0 = [ security(Security),
+                    port(Port),
+                    host(Host),
+                    hostname(HostName)
+                  ],
+    add_auth_method(DefOptions0, DefOptions1),
+    add_from(DefOptions1, DefOptions),
+    merge_options(DefOptions, Options, Options1),
+    debug( smtp, 'Starting smtp with options: ~w', [Options] ),
+    setup_call_cleanup(
+        smtp_open(Host:Port, In, Out, Options1),
+        do_send_mail(In, Out, To, Goal, Options1),
+        smtp_close(In, Out)).
+
+add_auth_method(Options0, Options) :-
+    (   setting(auth_method, AuthMethod),
+        AuthMethod \== default
+    ->  Options = [auth_method(AuthMethod)|Options0]
+    ;   Options = Options0
+    ).
+
+add_from(Options0, Options) :-
+    (   setting(from, From),
+        From \== ''
+    ->  Options = [from(From)|Options0]
+    ;   Options = Options0
+    ).
+
+%!  hostname(-HostName, +Options) is det.
+%
+%   Get the hostname used to identify me.
+
+hostname(HostName, Options) :-
+    option(hostname(HostName), Options),
+    !.
+hostname(HostName, _) :-
+    setting(hostname, HostName), HostName \== '',
+    !.
+hostname(HostName, _) :-
+    gethostname(HostName).
+
+default_port(_, DefPort, DefPort) :-
+    DefPort > 0,
+    !.
+default_port(none,      _,  25).
+default_port(ssl,       _, 465).
+default_port(tls,       _, 465).
+default_port(starttls,  _, 587).
+
+smtp_open(Address, In, Out, Options) :-
+    setup_call_error_cleanup(
+        tcp_socket(Socket),
+        tcp_connect(Socket, Address),
+        tcp_close_socket(Socket)),
+    setup_call_error_cleanup(
+        tcp_open_socket(Socket, In0, Out0),
+        setup_ssl(Address, In0, Out0, In, Out, Options),
+        smtp_close(In0, Out0)),
+    !.
+smtp_open(Address, _In, _Out, Options) :-
+    debug(smtp, 'Failed to open connection at address: ~w, \c
+                     with options: ~w', [Address,Options] ),
+    fail.
+
+setup_ssl(Address, In0, Out0, In, Out, Options) :-
+    option(security(Security), Options),
+    ssl_security(Security),
+    !,
+    Address = Host:_Port,
+    ssl_context(client, SSL,
+                [ host(Host),
+                  cert_verify_hook(cert_accept_any),
+                  close_parent(true)
+                ]),
+    ssl_negotiate(SSL, In0, Out0, In, Out).
+setup_ssl(_, In, Out, In, Out, _Options).
+
+ssl_security(ssl).
+ssl_security(tls).
+
+smtp_close(In, Out) :-
+    call_cleanup(close(Out), close(In)).
+
+setup_call_error_cleanup(Setup, Goal, Cleanup) :-
+    setup_call_catcher_cleanup(
+        Setup, Goal, Catcher, error_cleanup(Catcher, Cleanup)).
+
+error_cleanup(exit, _) :- !.
+error_cleanup(!, _) :- !.
+error_cleanup(_, Cleanup) :-
+    call(Cleanup).
+
+%!  do_send_mail(+In, +Out, +To, :Goal, +Options) is det.
+%
+%   Perform the greeting and possibly upgrade   to TLS. Then proceed
+%   using do_send_mail_cont/5.
+%
+%   Note that HELO is the old   SMTP  greeting. Modern systems greet
+%   using EHLO, telling the other side they   want to speak RFC 1870
+%   rather than the old RFC 821.
+%
+%   @tbd    Fall back to RFC 821 if the server does not understand
+%           EHLO.  Probably not needed anymore?
+
+do_send_mail(In, Out, To, Goal, Options) :-
+    read_ok(In, 220),
+    option(hostname(Me), Options),
+    sock_send(Out, 'EHLO ~w\r\n', [Me]),
+    read_ok(In, 250, Lines),
+    setup_call_cleanup(
+        starttls(In, Out, In1, Out1, Lines, Lines1, Options),
+        do_send_mail_cont(In1, Out1, To, Goal, Lines1, Options),
+        close_tls(In, Out, In1, Out1)).
+
+close_tls(In, Out, In, Out) :- !.
+close_tls(_, _, In, Out) :-
+    smtp_close(In, Out).
+
+do_send_mail_cont(In, Out, To, Goal, Lines, Options) :-
+    (   option(from(From), Options)
+    ->  true
+    ;   existence_error(smtp_option, from)
+    ),
+    auth(In, Out, From, Lines, Options),
+    sock_send(Out, 'MAIL FROM:<~w>\r\n', [From]),
+    read_ok(In, 250),
+    sock_send(Out, 'RCPT TO:<~w>\r\n', [To]),
+    read_ok(In, 250),
+    sock_send(Out, 'DATA\r\n', []),
+    read_ok(In, 354),
+    format(Out, 'To: ~w\r\n', [To]),
+    header_options(Out, Options),
+    sock_send(Out, '\r\n', []),
+    call(Goal, Out),
+    sock_send(Out, '\r\n.\r\n', []),
+    read_ok(In, 250),
+    !.
+do_send_mail_cont(_In, _Out, To, _Goal, _Lines, Options ) :-
+    debug(smtp, 'Failed to sent email To: ~w, with options: ~w',
+          [To,Options]),
+    fail.
+
+%!  starttls(+In0, +Out0, -In, -Out, +LinesIn, -LinesOut, +Options)
+%
+%   @tbd    Verify starttls is in Lines.
+
+starttls(In0, Out0, In, Out, _Lines, Lines, Options) :-
+    option(security(starttls), Options),
+    !,
+    option(host(Host), Options),
+    option(port(Port), Options),
+    sock_send(Out0, 'STARTTLS\r\n', []),
+    read_ok(In0, 220),
+    ssl_context(client, SSL,
+                [ host(Host),
+                  port(Port),
+                  cert_verify_hook(cert_accept_any)
+                ]),
+    ssl_negotiate(SSL, In0, Out0, In, Out),
+    option(hostname(Me), Options),
+    sock_send(Out, 'EHLO ~w\r\n', [Me]),
+    read_ok(In, 250, Lines).
+starttls(In, Out, In, Out, Lines, Lines, _).
+
+
+%!  auth(+In, +Out, +From, +Lines, +Options)
+%
+%   Negotiate authentication with the server. Currently supports the
+%   =plain= and =login=  authentication   methods.  Authorization is
+%   sent if the option =auth= is given   or  the settings =user= and
+%   =password= are not the empty atom ('').
+%
+%   @param  Lines is the result of read_ok/3 on the EHLO command,
+%           which tells us which authorizations are supported.
+
+auth(In, Out, From, Lines, Options) :-
+    (   option(auth(Auth), Options)
+    ;   setting(user, User), User \== '',
+        setting(password, Password), Password \== '',
+        Auth = User-Password
+    ),
+    !,
+    auth_supported(Lines, Supported),
+    debug( smtp, 'Authentications supported: ~w, with options: ~w', [Supported,Options] ),
+    auth_p(In, Out, From, Auth, Supported, Options).
+auth(_, _, _, _, _).
+
+auth_p(In, Out, From, User-Password, Protocols, Options) :-
+    memberchk(plain, Protocols),
+    \+ option(auth_method(login), Options),
+    !,
+    atom_codes(From, FromCodes),
+    atom_codes(User, UserCodes),
+    atom_codes(Password, PwdCodes),
+    append([FromCodes, [0], UserCodes, [0], PwdCodes], Plain),
+    phrase(base64(Plain), Encoded),
+    sock_send(Out, 'AUTH PLAIN ~s\r\n', [Encoded]),
+    read_ok(In, 235).
+auth_p(In, Out, _From, User-Password, Protocols, _Options) :-
+    memberchk(login, Protocols),
+    !,
+    sock_send(Out, 'AUTH LOGIN\r\n', []),
+    read_ok(In, 334),
+    base64(User, User64),
+    sock_send(Out, '~w\r\n', [User64]),
+    read_ok(In, 334),
+    base64(Password, Password64),
+    sock_send(Out, '~w\r\n', [Password64]),
+    read_ok(In, 235).
+auth_p(_In, _Out, _From, _Auth, _Protocols, _Options) :-
+    representation_error(smtp_auth).
+
+%!  auth_supported(+Lines, -Supported)
+%
+%   True  when  Supported  is  a  list  of  supported  authorization
+%   protocols.
+
+auth_supported(Lines, Supported) :-
+    member(Line, Lines),
+    downcase_atom(Line, Lower),
+    atom_codes(Lower, Codes),
+    phrase(auth(Supported), Codes),
+    !.
+
+auth(Supported) -->
+    "auth", white, whites,
+    !,
+    auth_list(Supported).
+
+auth_list([H|T]) -->
+    nonblanks(Protocol), {Protocol \== []},
+    !,
+    whites,
+    { atom_codes(H, Protocol)
+    },
+    auth_list(T).
+auth_list([]) -->
+    whites.
+
+%!  sock_send(+Stream, +Format, +Args) is det.
+%
+%   Send the output of format(Format, Args)  to Stream and flush the
+%   stream.
+
+sock_send(Stream, Fmt, Args) :-
+    format(Stream, Fmt, Args),
+    flush_output(Stream).
+
+%!  header_options(+Out, +Options) is det.
+%
+%   Send  SMTP  headers  from  provided  Options.  First  adds  some
+%   defaults, notably:
+%
+%     - If there is no header(from(From)) it uses the from(From)
+%       from Options.
+%     - If there is no date(Spec) it adds date(Date).
+
+header_options(Out, Options) :-
+    add_default_header(Options, Options1),
+    emit_header(Options1, Out).
+
+add_default_header(Options0, Options) :-
+    add_date_header(Options0, Options1),
+    add_from_header(Options1, Options2),
+    add_content_type_header(Options2, Options).
+
+add_from_header(Options0, Options) :-
+    (   option(header(from(_)), Options0)
+    ->  Options = Options0
+    ;   option(from(From), Options0)
+    ->  Options = [header(from(From))|Options0]
+    ;   Options = Options0
+    ).
+
+add_date_header(Options0, Options) :-
+    (   option(date(_), Options0)
+    ->  Options = Options0
+    ;   Options = [date(now)|Options0]
+    ).
+
+add_content_type_header(Options0, Options) :-
+    (   option(content_type(_), Options0)
+    ->  Options = Options0
+    ;   Options = [content_type(text/plain)|Options0]
+    ).
+
+
+emit_header([], _).
+emit_header([H|T], Out) :-
+    header_option(H, Out),
+    emit_header(T, Out).
+
+header_option(H, Out) :-
+    H =.. [Name, Value],
+    header(Name, Label),
+    !,
+    format(Out, '~w: ~w\r\n', [Label, Value]).
+header_option(mailed_by(true), Out) :-
+    current_prolog_flag( version_data, swi(Maj,Min,Pat,_) ),
+    atomic_list_concat( [Maj,Min,Pat], '.', Vers ),
+    !,
+    format(Out, 'X-Mailer: SWI-Prolog ~a, pack(smtp)\r\n', [Vers]).
+header_option(date(Date), Out) :-
+    (   Date == now
+    ->  get_time(Time)
+    ;   Time = Date
+    ),
+    format_time(string(String), '%a, %d %b %Y %T %z', Time),
+    format(Out, 'Date: ~w\r\n', [String]).
+header_option(header(Hdr), Out) :-
+    Hdr =.. [HdrName, Value],
+    header_key_upcase(HdrName, HdrAtom),
+    !,
+    format(Out, '~w: ~w\r\n', [HdrAtom, Value]).
+header_option(_, _).
+
+header(subject, 'Subject').
+header(content_type, 'Content-Type').
+
+header_key_upcase(Name, Atom) :-
+    sub_atom( Name, 0, 1, _, FirstOfName),
+    upcase_atom(FirstOfName, FirstOfAtom),
+    FirstOfAtom \== FirstOfName,
+    !,
+    sub_atom(Name, 1, _, 0, Unchanged),
+    atom_concat(FirstOfAtom, Unchanged, Atom).
+header_key_upcase(Name, Name).
+
+
+%!  read_ok(+Stream, ?Code) is semidet.
+%!  read_ok(+Stream, ?Code, -Lines) is semidet.
+%
+%   True if the server replies  with   Code.  The  version read_ok/3
+%   returns the server comment lines, one atom per line. The numeric
+%   code has been stripped from the lines.
+
+read_ok(Stream, Code) :-
+    read_ok(Stream, Code, _Reply).
+
+read_ok(Stream, Code, [Line|Rest]) :-
+    read_line_to_codes(Stream, Codes),
+    parse_line(Codes, Code, Line, Cont),
+    (   Cont == true
+    ->  read_reply_cont(Stream, Code, Rest)
+    ;   Rest = []
+    ).
+
+read_reply_cont(Stream, Code, [Line|Rest]) :-
+    read_line_to_codes(Stream, Codes),
+    parse_line(Codes, Code1, Line, Cont),
+    assertion(Code == Code1),
+    (   Cont == true
+    ->  read_reply_cont(Stream, Code, Rest)
+    ;   Rest = []
+    ).
+
+parse_line(Codes, Code, Line, Cont) :-
+    phrase(reply_line(Code,Line,Cont), Codes),
+    !.
+parse_line(Codes, _, _, _) :-
+    atom_codes(Atom, Codes),
+    throw(error(smtp_error(unexpected_reply(Atom)), _)).
+
+reply_line(Code, Line, Cont) -->
+    integer(Code),
+    (   "-"
+    ->  {Cont = true}
+    ;   " "
+    ->  {Cont = false}
+    ),
+    remainder(LineCodes),
+    { atom_codes(Line, LineCodes) }.
+
diff --git a/lib/swish/page.pl b/lib/swish/page.pl
index 8900aab..c461fa0 100644
--- a/lib/swish/page.pl
+++ b/lib/swish/page.pl
@@ -3,7 +3,7 @@
     Author:        Jan Wielemaker
     E-mail:        J.Wielemaker@vu.nl
     WWW:           http://www.swi-prolog.org
-    Copyright (c)  2014-2016, VU University Amsterdam
+    Copyright (c)  2014-2017, VU University Amsterdam
     All rights reserved.
 
     Redistribution and use in source and binary forms, with or without
@@ -39,6 +39,9 @@
 	    swish_navbar//1,			% +Options
 	    swish_content//1,			% +Options
 
+	    pengine_logo//1,			% +Options
+	    swish_logo//1,			% +Options
+
 	    swish_resources//0,
 	    swish_js//0,
 	    swish_css//0
@@ -66,6 +69,9 @@
 :- use_module(config).
 :- use_module(help).
 :- use_module(search).
+:- use_module(chat).
+:- use_module(authenticate).
+:- use_module(pep).
 
 /** <module> Provide the SWISH application as Prolog HTML component
 
@@ -79,10 +85,10 @@ http:location(pldoc, swish(pldoc), [priority(100)]).
 :- http_handler(swish(.), swish_reply([]), [id(swish), prefix]).
 
 :- multifile
+	swish_config:logo//1,
 	swish_config:source_alias/2,
 	swish_config:reply_page/1,
-	swish_config:verify_write_access/3, % +Request, +File, +Options
-	swish_config:authenticate/2.	    % +Request, -User
+	swish_config:li_login_button//1.
 
 %%	swish_reply(+Options, +Request)
 %
@@ -99,12 +105,12 @@ http:location(pldoc, swish(pldoc), [priority(100)]).
 %	  of a line.
 %	  - q(Query)
 %	  Use Query as the initial query.
+%	  - show_beware(Boolean)
+%	  Control showing the _beware limited edition_ warning.
 
 swish_reply(Options, Request) :-
-	swish_config:authenticate(Request, User), !, % must throw to deny access
-	swish_reply2([user(User)|Options], Request).
-swish_reply(Options, Request) :-
-	swish_reply2(Options, Request).
+	authenticate(Request, Auth),
+	swish_reply2([identity(Auth)|Options], Request).
 
 swish_reply2(Options, Request) :-
 	option(method(Method), Request),
@@ -115,18 +121,20 @@ swish_reply2(_, Request) :-
 swish_reply2(Options, Request) :-
 	swish_reply_config(Request, Options), !.
 swish_reply2(SwishOptions, Request) :-
-	Params = [ code(_,	 [optional(true)]),
-		   background(_, [optional(true)]),
-		   examples(_,   [optional(true)]),
-		   q(_,          [optional(true)]),
-		   format(_,     [oneof([swish,raw,json]), default(swish)])
+	Params = [ code(_,	  [optional(true)]),
+		   show_beware(_, [optional(true)]),
+		   background(_,  [optional(true)]),
+		   examples(_,    [optional(true)]),
+		   q(_,           [optional(true)]),
+		   format(_,      [oneof([swish,raw,json]), default(swish)])
 		 ],
 	http_parameters(Request, Params),
 	params_options(Params, Options0),
 	merge_options(Options0, SwishOptions, Options1),
-	source_option(Request, Options1, Options2),
-	option(format(Format), Options2),
-	swish_reply3(Format, Options2).
+	add_show_beware(Options1, Options2),
+	source_option(Request, Options2, Options3),
+	option(format(Format), Options3),
+	swish_reply3(Format, Options3).
 
 swish_reply3(raw, Options) :-
 	option(code(Code), Options), !,
@@ -135,7 +143,8 @@ swish_reply3(raw, Options) :-
 swish_reply3(json, Options) :-
 	option(code(Code), Options), !,
 	option(meta(Meta), Options, _{}),
-	reply_json_dict(json{data:Code, meta:Meta}).
+	option(chat_count(Count), Options, 0),
+	reply_json_dict(json{data:Code, meta:Meta, chats:_{count:Count}}).
 swish_reply3(_, Options) :-
 	swish_config:reply_page(Options), !.
 swish_reply3(_, Options) :-
@@ -160,6 +169,31 @@ params_options([H0|T0], [H|T]) :-
 params_options([_|T0], T) :-
 	params_options(T0, T).
 
+%!	add_show_beware(+Options0, -Option) is det.
+%
+%	Add show_beware(false) when called with code, query or examples.
+%	These are dedicated calls that do not justify this message.
+
+add_show_beware(Options0, Options) :-
+	implicit_no_show_beware(Options0), !,
+	Options = [show_beware(false)|Options0].
+add_show_beware(Options, Options).
+
+implicit_no_show_beware(Options) :-
+	option(show_beware(_), Options), !,
+	fail.
+implicit_no_show_beware(Options) :-
+	\+ option(format(swish), Options), !,
+	fail.
+implicit_no_show_beware(Options) :-
+	option(code(_), Options).
+implicit_no_show_beware(Options) :-
+	option(q(_), Options).
+implicit_no_show_beware(Options) :-
+	option(examples(_), Options).
+implicit_no_show_beware(Options) :-
+	option(background(_), Options).
+
 
 %%	source_option(+Request, +Options0, -Options)
 %
@@ -308,11 +342,20 @@ swish_navbar(Options) -->
 		   div([ class([collapse, 'navbar-collapse']),
 			 id(navbar)
 		       ],
-		       [ ul([class([nav, 'navbar-nav'])], []),
-			 \search_form(Options)
+		       [ ul([class([nav, 'navbar-nav', menubar])], []),
+			 ul([class([nav, 'navbar-nav', 'navbar-right'])],
+			    [ li(\notifications(Options)),
+			      li(\search_box(Options)),
+			      \li_login_button(Options)
+			    ])
 		       ])
 		 ])).
 
+li_login_button(Options) -->
+	swish_config:li_login_button(Options).
+li_login_button(_Options) -->
+	[].
+
 collapsed_button -->
 	html(button([type(button),
 		     class('navbar-toggle'),
@@ -325,10 +368,25 @@ collapsed_button -->
 		      span(class('icon-bar'), [])
 		    ])).
 
+swish_logos(Options) -->
+	swish_config:logo(Options), !.
 swish_logos(Options) -->
 	pengine_logo(Options),
 	swish_logo(Options).
 
+%!	swish_config:logo(+Options)// is semidet.
+%
+%	Hook  to  include  the  top-left    logos.   The  default  calls
+%	pengine_logo//1 and swish_logo//1.  The   implementation  should
+%	emit zero or more <a> elements.
+
+%!	pengine_logo(+Options)// is det.
+%!	swish_logo(+Options)// is det.
+%
+%	Emit an <a> element that provides a   link to Pengines and SWISH
+%	on this server. These may be called from swish_config:logo//1 to
+%	include the default logos.
+
 pengine_logo(_Options) -->
 	{ http_absolute_location(root(.), HREF, [])
 	},
@@ -338,14 +396,6 @@ swish_logo(_Options) -->
 	},
 	html(a([href(HREF), class('swish-logo')], &(nbsp))).
 
-%%	search_form(+Options)//
-%
-%	Add search box to the navigation bar
-
-search_form(Options) -->
-	html(div(class(['pull-right']),
-		 \search_box(Options))).
-
 
 %%	swish_content(+Options)//
 %
@@ -354,12 +404,15 @@ search_form(Options) -->
 %
 %	  - source(HREF)
 %	  Load initial source from HREF
+%	  - chat_count(Count)
+%	  Indicate the presense of Count chat messages
 
 swish_content(Options) -->
 	{ document_type(Type, Options)
 	},
 	swish_resources,
 	swish_config_hash(Options),
+	swish_options(Options),
 	html(div([id(content), class([container, swish])],
 		 [ div([class([tile, horizontal]), 'data-split'('50%')],
 		       [ div([ class([editors, tabbed])
@@ -391,6 +444,24 @@ swish_config_hash(Options) -->
 		   |}).
 
 
+%!	swish_options(+Options)//
+%
+%	Emit additional options. This is  similar   to  config,  but the
+%	config object is big and stable   for a particular SWISH server.
+%	The options are set per session.
+
+swish_options(Options) -->
+	{ option(show_beware(Show), Options),
+	  JSShow = @(Show)
+	}, !,
+	js_script({|javascript(JSShow)||
+		   window.swish = window.swish||{};
+		   window.swish.option = window.swish.options||{};
+		   window.swish.option.show_beware = JSShow;
+		   |}).
+swish_options(_Options) -->
+	[].
+
 %%	source(+Type, +Options)//
 %
 %	Associate the source with the SWISH   page. The source itself is
@@ -429,7 +500,8 @@ source_data_attrs(Options) -->
 	(source_url_data(Options) -> [] ; []),
 	(source_title_data(Options) -> [] ; []),
 	(source_meta_data(Options) -> [] ; []),
-	(source_st_type_data(Options) -> [] ; []).
+	(source_st_type_data(Options) -> [] ; []),
+	(source_chat_data(Options) -> [] ; []).
 
 source_file_data(Options) -->
 	{ option(file(File), Options) },
@@ -448,6 +520,11 @@ source_meta_data(Options) -->
 	  atom_json_dict(Text, Meta, [])
 	},
 	['data-meta'(Text)].
+source_chat_data(Options) -->
+	{ option(chat_count(Count), Options),
+	  atom_json_term(JSON, _{count:Count}, [as(string)])
+	},
+	['data-chats'(JSON)].
 
 %%	background(+Options)//
 %
@@ -495,7 +572,7 @@ notebooks(swinb, Options) -->
 	  download_source(Spec, NoteBookText, Options),
 	  phrase(source_data_attrs(Options), Extra)
 	},
-	html(div([ class('notebook fullscreen'),
+	html(div([ class('notebook'),
 		   'data-label'('Notebook')		% Use file?
 		 ],
 		 [ pre([ class('notebook-data'),
@@ -651,8 +728,8 @@ swish_rest_reply(put, Request, Options) :-
 	source_file(Request, File, Options1), !,
 	option(content_type(String), Request),
 	http_parse_header_value(content_type, String, Type),
-	read_data(Type, Request, Data, _Meta),
-	verify_write_access(Request, File, Options1),
+	read_data(Type, Request, Data, Meta),
+	authorized(file(update(File,Meta)), Options1),
 	setup_call_cleanup(
 	    open(File, write, Out),
 	    format(Out, '~s', [Data]),
@@ -665,20 +742,3 @@ read_data(media(Type,_), Request, Data, Meta) :-
 	del_dict(data, Dict, Data, Meta).
 read_data(media(text/_,_), Request, Data, _{}) :-
 	http_read_data(Request, Data, [to(string)]).
-
-%%	swish_config:verify_write_access(+Request, +File, +Options) is
-%%	nondet.
-%
-%	Hook that verifies that the HTTP Request  may write to File. The
-%	hook must succeed to grant access. Failure   is  is mapped to an
-%	HTTP _403 Forbidden_ reply. The  hook   may  throw  another HTTP
-%	reply.  By default, the following options are passed:
-%
-%	  - alias(+Alias)
-%	    The swish_config:source_alias/2 Alias used to find File.
-
-verify_write_access(Request, File, Options) :-
-	swish_config:verify_write_access(Request, File, Options), !.
-verify_write_access(Request, _File, _Options) :-
-	option(path(Path), Request),
-	throw(http_reply(forbidden(Path))).
diff --git a/lib/swish/paths.pl b/lib/swish/paths.pl
new file mode 100644
index 0000000..02f262a
--- /dev/null
+++ b/lib/swish/paths.pl
@@ -0,0 +1,109 @@
+/*  Part of SWISH
+
+    Author:        Jan Wielemaker
+    E-mail:        J.Wielemaker@cs.vu.nl
+    WWW:           http://www.swi-prolog.org
+    Copyright (C): 2017, VU University Amsterdam
+			 CWI Amsterdam
+    All rights reserved.
+
+    Redistribution and use in source and binary forms, with or without
+    modification, are permitted provided that the following conditions
+    are met:
+
+    1. Redistributions of source code must retain the above copyright
+       notice, this list of conditions and the following disclaimer.
+
+    2. Redistributions in binary form must reproduce the above copyright
+       notice, this list of conditions and the following disclaimer in
+       the documentation and/or other materials provided with the
+       distribution.
+
+    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
+    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
+    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
+    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
+    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
+    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
+    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
+    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
+    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
+    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
+    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
+    POSSIBILITY OF SUCH DAMAGE.
+*/
+
+:- module(swish_paths, []).
+:- use_module(library(http/http_path), []).
+
+/** <module> Setup SWISH search paths
+*/
+
+:- initialization initialize_paths.
+
+:- multifile
+    user:file_search_path/2,
+    http:location/3.
+
+user:file_search_path(data,           data).
+user:file_search_path(config_enabled, swish('config-enabled')).
+user:file_search_path(config,         config_enabled(.)).
+user:file_search_path(config,         swish('config-available')).
+user:file_search_path(swish_web,      swish(web)).
+user:file_search_path(swish_pack,     swish(pack)).
+user:file_search_path(js,             swish_web(js)).
+user:file_search_path(css,            swish_web(css)).
+user:file_search_path(icons,          swish_web(icons)).
+
+%!  set_swish_path
+%
+%   Setup the swish search path.
+
+set_swish_path :-
+    absolute_file_name(swish('swish.pl'), _,
+                       [file_errors(fail), access(read)]), !.
+set_swish_path :-
+    prolog_load_context(directory, Dir),
+    asserta(user:file_search_path(swish, Dir)).
+
+%!  attach_local_packs
+%
+%   Attach pack submodules from swish(pack)
+
+attach_local_packs :-
+    attach_packs(swish_pack(.), [duplicate(replace), search(first)]).
+
+%!  set_data_path
+%
+%   Setup and possibly create a directory for storing dynamic data.
+
+set_data_path :-
+    absolute_file_name(data(.), _,
+                       [ file_type(directory),
+                         access(write),
+                         file_errors(fail)
+                       ]), !.
+set_data_path :-
+    absolute_file_name(data(.), Dir,
+                       [ solutions(all)
+                       ]),
+    \+ exists_directory(Dir),
+    catch(make_directory(Dir),
+          error(permission_error(create,directory,Dir), _),
+          fail), !,
+    print_message(informational, swish(created_data_dir(Dir))).
+set_data_path :-
+    print_message(error, swish(no_data_dir)),
+    halt(1).
+
+initialize_paths :-
+    set_swish_path,
+    attach_local_packs,
+    set_data_path.
+
+% HTTP paths
+
+http:location(swish, root(.), [priority(-100)]).
+
+
+
diff --git a/lib/swish/pep.pl b/lib/swish/pep.pl
new file mode 100644
index 0000000..cf64821
--- /dev/null
+++ b/lib/swish/pep.pl
@@ -0,0 +1,152 @@
+/*  Part of SWISH
+
+    Author:        Jan Wielemaker
+    E-mail:        J.Wielemaker@cs.vu.nl
+    WWW:           http://www.swi-prolog.org
+    Copyright (C): 2017, VU University Amsterdam
+			 CWI Amsterdam
+    All rights reserved.
+
+    Redistribution and use in source and binary forms, with or without
+    modification, are permitted provided that the following conditions
+    are met:
+
+    1. Redistributions of source code must retain the above copyright
+       notice, this list of conditions and the following disclaimer.
+
+    2. Redistributions in binary form must reproduce the above copyright
+       notice, this list of conditions and the following disclaimer in
+       the documentation and/or other materials provided with the
+       distribution.
+
+    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
+    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
+    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
+    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
+    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
+    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
+    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
+    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
+    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
+    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
+    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
+    POSSIBILITY OF SUCH DAMAGE.
+*/
+
+:- module(swish_pep,
+          [ authorized/2                               % +Request, +Action
+          ]).
+:- use_module(library(debug)).
+:- use_module(library(option)).
+:- use_module(library(error)).
+:- use_module(library(http/http_wrapper)).
+
+:- use_module(authenticate).
+:- use_module(storage).
+:- use_module(config).
+
+/** <module> SWISH PEP (Policy Enforcement Point)
+
+This module implements the _Policy Enforcement   Point_. It is called by
+modules that perform operations that may   not be publically accessible.
+Examples are:
+
+  - Access to files (download, create, update, delete, list, search)
+  - Control of the sandboxing
+  - Access to users (profile management)
+*/
+
+:- multifile
+    swish_config:approve/2,
+    swish_config:deny/2.
+
+%!  authorized(+Action, +Options) is det.
+%
+%   Verify that Action is authorized.  Options:
+%
+%     - indentity(+Identity)
+%       Indentity is the identity dict as collected by autenticate.pl.
+%
+%   Actions defined:
+%
+%     * Gitty store actions
+%       - gitty(download(Obj, Format))
+%         Attempt to download Obj, one of file(File) or hash(Hash) in
+%         Format, see storage_get/4 from storage.pl
+%       - gitty(create(File,Named,Meta))
+%         Create file name File with the given meta-data.  Named is one
+%         of `named` or `random` and indicates whether the file is named
+%         by the user or the name is generated by the system.
+%       - gitty(update(File,PrevMeta,Meta))
+%         Update File and change meta-data from PrevMeta to Meta.
+%       - gitty(delete(File,Meta))
+%         Delete File that has the given meta data.
+%     * File actions
+%       - file(update(File,Meta))
+%         Update (save) a physical file outside the versioned gitty
+%         store.
+%     * Social options
+%       - chat
+%         Open websocket chat channel
+%
+%   @throws http_reply(forbidden(URL)) if the action is not allowed. Can
+%   we generate a JSON error object?
+
+authorized(Action, _Options) :-
+    var(Action),
+    !,
+    instantiation_error(Action).
+authorized(Action, Options) :-
+    option(identity(Id), Options),
+    (   authorize(Action, Id)
+    ->  debug(pep, 'Approved gitty action ~p to ~p', [Action, Id])
+    ;   debug(pep, 'Denied action ~p to ~p', [Action, Id]),
+        http_current_request(Request),
+        option(path(Path), Request),
+        throw(http_reply(forbidden(Path)))
+    ).
+
+:- multifile
+    approve/2,
+    deny/2.
+
+authorize(Action, Id) :-
+    approve(Action, Id), !,
+    \+ deny(Action, Id).
+
+%!  approve(+Action, +Id)
+
+approve(gitty(update(_File,PrevMeta,_Meta)), Auth) :- !,
+    storage_meta_property(PrevMeta, modify(Modify)),
+    (   memberchk(any, Modify)
+    ->  true
+    ;   memberchk(login, Modify)
+    ->  user_property(Auth, login(_))
+    ;   storage_meta_property(PrevMeta, identity(Id)),
+        user_property(Auth, identity(Id))
+    ).
+approve(gitty(_), _).
+approve(file(update(_File, _Meta)), Auth) :-
+    user_property(Auth, login(local)).
+approve(run(any, _), Auth) :-
+    user_property(Auth, login(local)).
+approve(chat, _).
+
+%!  deny(+Auth, +Id)
+
+
+
+
+		 /*******************************
+		 *           PENGINES		*
+		 *******************************/
+
+%!  pengines:not_sandboxed(+User, +Application) is semidet.
+%
+%   Called by Pengines to  see  whether   User  may  call  non-sandboxed
+%   operations in Application.
+
+:- multifile pengines:not_sandboxed/2.
+
+pengines:not_sandboxed(User, Application) :-
+    authorized(run(any, Application), [identity(User)]).
diff --git a/lib/swish/plugin/email.pl b/lib/swish/plugin/email.pl
new file mode 100644
index 0000000..a789722
--- /dev/null
+++ b/lib/swish/plugin/email.pl
@@ -0,0 +1,352 @@
+/*  Part of SWISH
+
+    Author:        Jan Wielemaker
+    E-mail:        J.Wielemaker@cs.vu.nl
+    WWW:           http://www.swi-prolog.org
+    Copyright (C): 2017, VU University Amsterdam
+			 CWI Amsterdam
+    All rights reserved.
+
+    Redistribution and use in source and binary forms, with or without
+    modification, are permitted provided that the following conditions
+    are met:
+
+    1. Redistributions of source code must retain the above copyright
+       notice, this list of conditions and the following disclaimer.
+
+    2. Redistributions in binary form must reproduce the above copyright
+       notice, this list of conditions and the following disclaimer in
+       the documentation and/or other materials provided with the
+       distribution.
+
+    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
+    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
+    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
+    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
+    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
+    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
+    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
+    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
+    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
+    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
+    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
+    POSSIBILITY OF SUCH DAMAGE.
+*/
+
+:- module(swish_email,
+          [ smtp_send_mail/3,           % +To, :Goal, +Options
+            smtp_send_html/3,           % +To, :Content, +Options
+
+            dear//1,                    % +ProfileID
+            signature//0,
+            profile_name//1,            % +ProfileID
+            email_action_link//4,	% :Label, :Reply, :Action, +Options
+
+            email_style//0,             % Inline style sheet
+
+            email_cleanup_db/0,
+
+            public_url/4                % +To, +Query, -URL, +Options
+          ]).
+:- use_module(library(smtp)).           % from pack smtp
+:- use_module(library(option)).
+:- use_module(library(settings)).
+:- use_module(library(base64)).
+:- use_module(library(http/http_dispatch)).
+:- use_module(library(http/http_host)).
+:- use_module(library(http/html_write)).
+:- use_module(library(apply)).
+:- use_module(library(random)).
+:- use_module(library(persistency)).
+:- use_module(library(broadcast)).
+:- use_module(library(user_profile)).
+
+/** <module> Email plugin for SWISH
+
+This module deals with sending  email  from   SWISH.  Email  is sent for
+confirmation (of the email address) as well as for notifications.
+*/
+
+:- html_meta
+    smtp_send_html(+, html, +),
+    email_action_link(html, 1, 0, +, ?, ?).
+
+:- setting(timeout, integer, 24*3600*7,
+           "Timeout for handling email reply").
+:- setting(database, callable, swish('data/confirm.db'),
+           "File specification for E-mail confirmations").
+:- setting(subject_prefix, atom, '[SWISH] ',
+           "Prefix for the subject of emails sent").
+
+:- http_handler(swish('mail/action/'), on_mail_link,
+                [prefix, id(on_mail_link)]).
+
+
+		 /*******************************
+		 *            DATABASE		*
+		 *******************************/
+
+:- persistent
+        request(key:string,
+                deadline:integer,
+                action:callable,
+                reply:callable).
+
+email_open_db :-
+    db_attached(_),
+    !.
+email_open_db :-
+    setting(database, Spec),
+    absolute_file_name(Spec, Path, [access(write)]),
+    db_attach(Path, [sync(close)]).
+
+%!  email_cleanup_db
+%
+%   Strip the email confirmation queue from outdated messages.
+
+email_cleanup_db :-
+    with_mutex(swish_email, email_cleanup_db_sync).
+
+email_cleanup_db_sync :-
+    get_time(Now),
+    forall(( request(Key, Deadline, _, _),
+             Now > Deadline
+           ),
+           retract_request(Key, Deadline, _, _)),
+    db_sync(gc).
+
+
+
+		 /*******************************
+		 *           EMAIL		*
+		 *******************************/
+
+%!  smtp_send_html(+To, :Content, +Options)
+%
+%   Send an HTML mail to To  using   HTML  content  Content. Options are
+%   passed  to  smtp_send_mail/3,  passing    as   default  content-type
+%   `text/html`.
+
+smtp_send_html(To, Content, Options) :-
+    select_option(subject(Subject), Options, Options1, "<no subject>"),
+    setting(subject_prefix, Prefix),
+    string_concat(Prefix, Subject, Subject1),
+    merge_options(Options1,
+                  [ header('MIME-Version'('1.0')),
+                    content_type(text/html)
+                  ], Options2),
+    smtp_send_mail(To, html_body(Content),
+                   [ subject(Subject1)
+                   | Options2
+                   ]).
+
+html_body(Content, Out) :-
+    phrase(html(html([ head([]),
+                       body(Content)
+                     ])), Tokens),
+    print_html(Out, Tokens).
+
+%!  generate_key(-Key) is det.
+%
+%   Generate a random confirmation key
+
+generate_key(Key) :-
+    length(Codes, 16),
+    maplist(random_between(0,255), Codes),
+    phrase(base64url(Codes), Encoded),
+    string_codes(Key, Encoded).
+
+
+		 /*******************************
+		 *            STYLE		*
+		 *******************************/
+
+email_style -->
+    html({|html||
+<style>
+address { width: 80%; text-align: right;
+          margin-left: 18%; margin-top: 2em; border-top: 1px solid #888;}
+</style>
+         |}).
+
+
+
+		 /*******************************
+		 *         PAGE ELEMENTS	*
+		 *******************************/
+
+%!  dear(+Profile)//
+%
+%   Address user with the given ProfileID.
+
+dear(Profile) -->
+    html(p(['Dear ', \profile_name(Profile), ','])).
+
+%!  signature//
+%
+%   Emit footer
+
+signature -->
+    { host_url(HostURL, []) },
+    !,
+    html(address(['SWISH at ', a(href(HostURL), HostURL)])).
+signature -->
+    html(address(['SWISH'])).
+
+%!  profile_name(+Profile)//
+%
+%   Emit the name associated with Profile as unstyled HTML.
+
+profile_name(User) -->
+    { user_field(Field),
+      Term =.. [Field, Name],
+      profile_property(User, Term)
+    },
+    html(Name).
+
+user_field(name).
+user_field(given_name).
+user_field(nick_name).
+user_field(family_name).
+
+%!  mailto(+Address)//
+%
+%   Insert an email link, displaying the address itself.
+
+mailto(Address) -->
+    html(a(href('mailto:'+Address), Address)).
+
+
+		 /*******************************
+		 *         ACTIVE LINKS		*
+		 *******************************/
+
+%!  email_action_link(:Label, :Reply, :Action, +Options)//
+%
+%   Generate a link in an HTML mail   page  that, when clicked, executes
+%   Action and if successful replies to the request using Reply.
+
+email_action_link(Label, Reply, Action, Options) -->
+    { email_open_db,
+      generate_key(Key),
+      public_url(on_mail_link, path_postfix(Key), HREF, Options),
+      setting(timeout, TMODef),
+      option(timeout(TMO), Options, TMODef),
+      get_time(Now),
+      Deadline is round(Now+TMO),
+      with_mutex(swish_email,
+                 assert_request(Key, Deadline, Action, Reply))
+    },
+    html(a(href(HREF), Label)).
+
+%!  on_mail_link(Request)
+%
+%   React on a clicked link generated by email_action_link//4.
+
+on_mail_link(Request) :-
+    email_open_db,
+    option(path_info(Path), Request),
+    atom_string(Path, Key),
+    with_mutex(swish_email,
+               retract_request(Key, Deadline, Action, Reply)),
+    !,
+    (   get_time(Now),
+        Now =< Deadline
+    ->  call(Action),
+        call(Reply, Request)
+    ;   reply_expired(Request)
+    ).
+on_mail_link(Request) :-
+    email_open_db,
+    option(path_info(Path), Request),
+    atom_string(Path, Key),
+    reply_html_page(
+        email_confirmation,
+        title('Unknown request'),
+        [ \email_style,
+          p([ 'Cannot find request ~w.'-[Key], ' This typically means the \c
+               request has already been executed, is expired or the link \c
+               is invalid.'
+            ]),
+          \signature
+        ]).
+on_mail_link(_Request) :-
+    throw(http_reply(bad_request(missing_key))).
+
+reply_expired(_Request) :-
+    reply_html_page(
+        email_confirmation,
+        title('Request expired'),
+        [ \email_style,
+          p([ 'Your request has expired.'
+            ]),
+          \signature
+        ]).
+
+
+%!  public_url(+To, +Query, -URL, +Options) is det.
+%
+%   True when URL is a link to handler To with Query
+
+public_url(To, Query, URL, Options) :-
+    http_link_to_id(To, Query, RequestURI),
+    host_url(HostURL, Options),
+    atom_concat(HostURL, RequestURI, URL).
+
+host_url(HostURL, Options) :-
+    option(host_url(HostURL), Options),
+    !.
+host_url(HostURL, _Options) :-
+    http_public_host_url(_Request, HostURL).
+
+
+		 /*******************************
+		 *             EVENTS		*
+		 *******************************/
+
+:- listen(user_profile(modified(User, email, Old, New)),
+          email_verify(User, Old, New)).
+
+email_verify(_User, _Old, "") :-
+    !.
+email_verify(User, Old, Email) :-
+    smtp_send_html(Email, \email_verify(User, Old, Email),
+                   [ subject("Please verify email")
+                   ]).
+
+
+email_verify(User, "", New) -->
+    html([ \email_style,
+           \dear(User),
+           p(['We have received a request to set the email account \c
+               for SWISH to ', \mailto(New), '.' ]),
+           ul([ li(\confirm_link(User, New))
+              ]),
+           \signature
+         ]).
+email_verify(User, Old, New) -->
+    html([ \email_style,
+           \dear(User),
+           p(['We have received a request to change the email account \c
+               for SWISH from ', \mailto(Old), ' to ', \mailto(New), '.' ]),
+           ul([ li(\confirm_link(User, New))
+              ]),
+           \signature
+         ]).
+
+confirm_link(User, New) -->
+    email_action_link(["Verify email as ", New], verified_email(User, New),
+                      verify_email(User), []).
+
+verify_email(User) :-
+    set_profile(User, email_verified(true)).
+
+verified_email(User, NewEmail, _Request) :-
+    reply_html_page(
+        email_confirmation,
+        title('SWISH -- Email verified'),
+        [ \email_style,
+          \dear(User),
+          p(['Your email address ', \mailto(NewEmail), ' has been verified.']),
+          \signature
+        ]).
diff --git a/lib/swish/plugin/login.pl b/lib/swish/plugin/login.pl
new file mode 100644
index 0000000..2be41d1
--- /dev/null
+++ b/lib/swish/plugin/login.pl
@@ -0,0 +1,319 @@
+/*  Part of SWISH
+
+    Author:        Jan Wielemaker
+    E-mail:        J.Wielemaker@cs.vu.nl
+    WWW:           http://www.swi-prolog.org
+    Copyright (C): 2017, VU University Amsterdam
+                         CWI Amsterdam
+    All rights reserved.
+
+    Redistribution and use in source and binary forms, with or without
+    modification, are permitted provided that the following conditions
+    are met:
+
+    1. Redistributions of source code must retain the above copyright
+       notice, this list of conditions and the following disclaimer.
+
+    2. Redistributions in binary form must reproduce the above copyright
+       notice, this list of conditions and the following disclaimer in
+       the documentation and/or other materials provided with the
+       distribution.
+
+    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
+    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
+    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
+    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
+    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
+    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
+    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
+    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
+    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
+    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
+    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
+    POSSIBILITY OF SUCH DAMAGE.
+*/
+
+:- module(swish_login,
+          [ login_button//1,            % +Options
+            login_continue_button//0,
+            reply_logged_in/1,          % +Options
+            reply_logged_in_page/1,     % +Options
+            reply_logged_out/1,         % +Options
+            reply_logged_out_page/1,    % +Options
+            current_user_info/2         % +Request, -UserInfo
+          ]).
+:- use_module(library(http/http_dispatch)).
+:- use_module(library(http/http_parameters)).
+:- use_module(library(http/http_json)).
+:- use_module(library(http/html_write)).
+:- use_module(library(http/js_write)).
+:- use_module(library(option)).
+:- use_module(library(apply)).
+:- use_module(library(broadcast)).
+
+:- use_module('../config', []).
+
+:- multifile
+    swish_config:li_login_button//1,    % +Options
+    swish_config:reply_logged_in/1,     % +Options
+    swish_config:reply_logged_out/1,    % +Options
+    swish_config:user_info/3,           % +Request, -Server, -Info
+    swish_config:user_profile/2.        % +Request, -Info
+
+/** <module> SWISH login support
+
+This module provides the generic  code   to  deal  with _optional_ login
+using multiple protocols. _Optional_ means that   SWISH may be used both
+anonymously and after login.
+
+This module cooperates with web/js/login.js. Login providers are defined
+using configuration hooks. The various login options are accompagnied by
+configuration files in =config-available=.
+*/
+
+:- http_handler(swish(login),        swish_login,  [id(login)]).
+:- http_handler(swish(user_info),    user_info,    [id(user_info)]).
+
+
+		 /*******************************
+		 *          UI ELEMENTS		*
+		 *******************************/
+
+%!  swish_config:li_login_button(+Options)//
+%
+%   Hook called from page.pl to include the login buttons.
+
+swish_config:li_login_button(Options) -->
+    html(li(\login_button(Options))).
+
+%!  login_button(+Options)//
+%
+%   Add a login/logout button. This button is added if there is at least
+%   one option for optional login.
+
+login_button(_Options) -->
+    { findall(Item, login_item(Item), Items0),
+      Items0 \== [],
+      sort(Items0, Items),
+      http_link_to_id(login, [], Login)
+    },
+    !,
+    html(a([ href(Login), id(login), class(login) ],
+           [ span(class(login),
+                  \login_items(Items)),
+             span([ class(logout)
+                  ],
+                  [ span(class(value), 'Logout')
+                  ])
+           ])).
+login_button(_Options) -->              % config-available/auth_http_always.pl
+    html(a([ id(login), class([login, 'no-logout']) ],
+           [ span([ class(logout)
+                  ],
+                  [ span(class(value), [])
+                  ])
+           ])).
+
+login_item(item(Tag, Server, Item)) :-
+    swish_config:login_item(Server, Item0),
+    (   Item0 = Tag-Item
+    ->  true
+    ;   Item = Item0,
+        Tag = 0
+    ).
+
+%!  login_items(+Items)
+%
+%   Show the login options. If there is only   one, we just show a login
+%   field.
+
+login_items([item(_Tag, Server, Item)]) -->
+    !,
+    { findall(Attr, login_attr(Item, Attr), Attrs)
+    },
+    html(span(['data-server'(Server)|Attrs],
+              [ span(class([glyphicon, 'glyphicon-log-in']), []),
+                span(class(value), 'Login')
+              ])).
+login_items(Items) -->
+    { maplist(arg(3), Items, HTML) },
+    html([ span(class(value), HTML)
+         ]).
+
+login_attr(Item, 'data-frame'(Frame)) :-
+    sub_term('data-frame'(Frame), Item).
+
+
+
+
+%!  reply_logged_in(+Options) is det.
+%!  reply_logged_in_page(+Options) is det.
+%
+%   Reply with an HTML  document  that   the  login  succeeded.  This is
+%   normally called from the protocol-specific login handler to indicate
+%   that the login succeeded.  Options:
+%
+%     - identity_provider(+Provider)
+%     Indicate the identity provider that did the login.  Provider is
+%     a term for html//1.
+%     - user(+User)
+%     User id of the identified user.
+%     - name(+Name)
+%     Common name of the identified user.
+%     - user_info(+Dict)
+%     Information provided by the identity provider.
+%
+%   At least one of user(User) or name(Name) must be present.
+%
+%   The     predicate     reply_logged_in/1     calls     the     _hook_
+%   swish_config:reply_logged_in/1.   This   hook   is    provided   for
+%   interacting with a user profile manager.
+
+reply_logged_in(Options) :-
+    swish_config:reply_logged_in(Options),
+    !.
+reply_logged_in(Options) :-
+    reply_logged_in_page(Options).
+
+reply_logged_in_page(Options) :-
+    reply_html_page(
+        title('Logged in'),
+        [ h4('Welcome'),
+          p([ 'You have been identified ',
+              \identity_provider(Options),
+              ' as ',
+              \user(Options)
+            ]),
+          \login_continue_button
+        ]).
+
+identity_provider(Options) -->
+    { option(identity_provider(Provider), Options) },
+    !,
+    html(['by ', Provider]).
+identity_provider(_) --> [].
+
+user(Options) -->
+    { option(user(User), Options) },
+    !,
+    html(User),
+    (   { option(name(Name), Options) }
+    ->  html([' (', Name, ')' ])
+    ;   []
+    ).
+user(Options) -->
+    { option(name(Name), Options) },
+    !,
+    html(Name).
+user(_) -->
+    html(unknown).
+
+%!  login_continue_button//
+%
+%   The login page is opened either  inside   an  iframe  inside a SWISH
+%   modal dialog or inside a browser popup   window. This scripts adds a
+%   button to dismiss the browser popup window.
+
+login_continue_button -->
+    html(style(\[ 'div.login-continue { text-align: center; margin-top: 2em; }'
+                ])),
+
+    js_script({|javascript||
+function inIframe() {
+  try {
+    return window.self !== window.top;
+  } catch (e) {
+    return true;
+  }
+}
+
+function append( elString, parent ) {
+  var div = document.createElement( "div" );
+  div.innerHTML = elString;
+  document.querySelector( parent || "body" ).appendChild( div.firstChild );
+}
+
+if ( !inIframe() ) {
+  append('<div class="login-continue">\n'+
+         '  <button onclick="window.close()">\n'+
+         '    Continue\n'+
+         '  </button>\n'+
+         '</div>');
+}
+              |}).
+
+
+
+%!  reply_logged_out(+Options)
+%
+%   Perform pluggable logout
+
+reply_logged_out(Options) :-
+    swish_config:reply_logged_out(Options),
+    !.
+reply_logged_out(Options) :-
+    reply_logged_out_page(Options).
+
+reply_logged_out_page(Options) :-
+    option(reply(Format), Options, json),
+    (   Format == json
+    ->  reply_json_dict(true)
+    ;   true
+    ).
+
+
+		 /*******************************
+		 *          HTTP HANDLERS	*
+		 *******************************/
+
+%!  swish_login(+Request)
+%
+%   HTTP handler that deals with  login.   This  handler  is called from
+%   web/js/login.js which adds  the  selected   login  server  from  the
+%   =data-server= attribute.
+
+swish_login(Request) :-
+    http_parameters(Request,
+                    [ server(Server, [default(default)])
+                    ]),
+    swish_config:login(Server, Request).
+
+%!  user_info(+Request)
+%
+%   HTTP handler to obtain information on  the currently logged in user.
+%   This handler tries the clauses  dealing   with  login for a specific
+%   protocol.  This is called by login.update() from login.js.
+
+user_info(Request) :-
+    http_parameters(Request,
+                    [ reason(Reason, [optional(true)])
+                    ]),
+    (   current_user_info(Request, Info)
+    ->  reply_json_dict(Info)
+    ;   (   Reason == logout_by_http
+        ->  broadcast(swish(logout(http)))
+        ;   true
+        ),
+        reply_json_dict(null)
+    ).
+
+%!  current_user_info(+Request, -Info) is semidet.
+%
+%   If there is a logged in user, Info is a dict with information about
+%   this user.
+
+current_user_info(Request, Info) :-
+    swish_config:user_info(Request, _Server, UserInfo),
+    (   swish_config:user_profile(Request, Profile)
+    ->  copy_fields([identity_provider, auth_method, logout_url],
+                    UserInfo, Profile, Info)
+    ;   Info = UserInfo
+    ).
+
+copy_fields([], _From, Dict, Dict).
+copy_fields([H|T], From, Dict0, Dict) :-
+    (   V = From.get(H)
+    ->  copy_fields(T, From, Dict0.put(H,V), Dict)
+    ;   copy_fields(T, From, Dict0, Dict)
+    ).
+
diff --git a/lib/swish/plugin/notify.pl b/lib/swish/plugin/notify.pl
new file mode 100644
index 0000000..082fe52
--- /dev/null
+++ b/lib/swish/plugin/notify.pl
@@ -0,0 +1,795 @@
+/*  Part of SWISH
+
+    Author:        Jan Wielemaker
+    E-mail:        J.Wielemaker@cs.vu.nl
+    WWW:           http://www.swi-prolog.org
+    Copyright (C): 2017, VU University Amsterdam
+			 CWI Amsterdam
+    All rights reserved.
+
+    Redistribution and use in source and binary forms, with or without
+    modification, are permitted provided that the following conditions
+    are met:
+
+    1. Redistributions of source code must retain the above copyright
+       notice, this list of conditions and the following disclaimer.
+
+    2. Redistributions in binary form must reproduce the above copyright
+       notice, this list of conditions and the following disclaimer in
+       the documentation and/or other materials provided with the
+       distribution.
+
+    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
+    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
+    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
+    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
+    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
+    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
+    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
+    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
+    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
+    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
+    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
+    POSSIBILITY OF SUCH DAMAGE.
+*/
+
+:- module(swish_notify,
+          [ follow/3,                           % +DocID, +ProfileID, +Options
+            notify/2                            % +DocID, +Action
+          ]).
+:- use_module(library(settings)).
+:- use_module(library(persistency)).
+:- use_module(library(broadcast)).
+:- use_module(library(lists)).
+:- use_module(library(readutil)).
+:- use_module(library(debug)).
+:- use_module(library(error)).
+:- use_module(library(apply)).
+:- use_module(library(http/html_write)).
+:- use_module(library(http/http_session)).
+:- use_module(library(http/http_dispatch)).
+:- use_module(library(http/http_parameters)).
+:- use_module(library(http/http_json)).
+
+:- use_module(library(user_profile)).
+
+:- use_module(email).
+:- use_module('../bootstrap').
+:- use_module('../storage').
+:- use_module('../chat').
+
+/** <module> SWISH notifications
+
+This module keeps track of which users wish to track which notifications
+and sending the notifications to the user.  If the target user is online
+we will notify using an avatar.  Otherwise we send an email.
+
+A user has the following options to control notifications:
+
+  * Per (gitty) file
+    - Notify update
+    - Notify chat
+  * By profile
+    - Notify by E-mail: never/immediate/daily
+*/
+
+:- setting(database, callable, swish('data/notify.db'),
+           "Database holding notifications").
+:- setting(queue, callable, swish('data/notify-queue.db'),
+           "File holding queued messages").
+:- setting(daily, compound, 04:00,
+           "Time at which to send daily messages").
+
+:- meta_predicate try(0).
+
+		 /*******************************
+		 *            DATABASE		*
+		 *******************************/
+
+:- persistent
+        follower(docid:atom,
+                 profile:atom,
+                 options:list(oneof([update,chat]))).
+
+notify_open_db :-
+    db_attached(_),
+    !.
+notify_open_db :-
+    setting(database, Spec),
+    absolute_file_name(Spec, Path, [access(write)]),
+    db_attach(Path, [sync(close)]).
+
+%!  queue_event(+Profile, +DocID, +Action) is det.
+%!  queue_event(+Profile, +DocID, +Action, +Status) is det.
+%
+%   Queue an email notification for  Profile,   described  by Action. We
+%   simply append these events as Prolog terms to a file.
+
+queue_event(Profile, DocID, Action) :-
+    queue_event(Profile, DocID, Action, new).
+queue_event(Profile, DocID, Action, Status) :-
+    queue_file(Path),
+    with_mutex(swish_notify,
+               queue_event_sync(Path, Profile, DocID, Action, Status)),
+    start_mail_scheduler.
+
+queue_event_sync(Path, Profile, DocID, Action, Status) :-
+    setup_call_cleanup(
+        open(Path, append, Out, [encoding(utf8)]),
+        format(Out, '~q.~n', [notify(Profile, DocID, Action, Status)]),
+        close(Out)).
+
+queue_file(Path) :-
+    setting(queue, Spec),
+    absolute_file_name(Spec, Path, [access(write)]).
+
+%!  send_queued_mails is det.
+%
+%   Send possible queued emails.
+
+send_queued_mails :-
+    queue_file(Path),
+    exists_file(Path), !,
+    atom_concat(Path, '.sending', Tmp),
+    with_mutex(swish_notify, rename_file(Path, Tmp)),
+    read_file_to_terms(Tmp, Terms, [encoding(utf8)]),
+    forall(member(Term, Terms),
+           send_queued(Term)),
+    delete_file(Tmp).
+send_queued_mails.
+
+send_queued(notify(Profile, DocID, Action, Status)) :-
+    profile_property(Profile, email(Email)),
+    profile_property(Profile, email_notifications(When)),
+    When \== never, !,
+    (   catch(send_notification_mail(Profile, DocID, Email, Action),
+              Error, true)
+    ->  (   var(Error)
+        ->  true
+        ;   update_status(Status, Error, NewStatus)
+        ->  queue_event(Profile, Action, NewStatus)
+        ;   true
+        )
+    ;   update_status(Status, failed, NewStatus)
+    ->  queue_event(Profile, DocID, Action, NewStatus)
+    ;   true
+    ).
+
+update_status(new, Status, retry(3, Status)).
+update_status(retry(Count0, _), Status, retry(Count, Status)) :-
+    Count0 > 0,
+    Count is Count0 - 1.
+
+%!  start_mail_scheduler
+%
+%   Start a thread that schedules queued mail handling.
+
+:- dynamic mail_scheduler_running/0.
+
+start_mail_scheduler :-
+    mail_scheduler_running,
+    !.
+start_mail_scheduler :-
+    catch(thread_create(mail_main, _,
+                        [ alias(mail_scheduler),
+                          detached(true),
+                          at_exit(retractall(mail_scheduler_running))
+                        ]),
+          error(permission_error(create, thread, mail_scheduler), _),
+          true).
+
+%!  mail_main
+%
+%   Infinite loop that schedules sending queued messages.
+
+mail_main :-
+    asserta(mail_scheduler_running),
+    repeat,
+    next_send_queue_time(T),
+    get_time(Now),
+    Sleep is T-Now,
+    sleep(Sleep),
+    thread_create(send_queued_mails, _,
+                  [ detached(true),
+                    alias(send_queued_mails)
+                  ]),
+    fail.
+
+next_send_queue_time(T) :-
+    get_time(Now),
+    stamp_date_time(Now, date(Y,M,D0,H0,_M,_S,Off,TZ,DST), local),
+    setting(daily, HH:MM),
+    (   H0 @< HH
+    ->  D = D0
+    ;   D is D0+1
+    ),
+    date_time_stamp(date(Y,M,D,HH,MM,0,Off,TZ,DST), T).
+
+
+%!  follow(+DocID, +ProfileID, +Flags) is det.
+%
+%   Assert that DocID is being followed by ProfileID using Flags.
+
+follow(DocID, ProfileID, Flags) :-
+    to_atom(DocID, DocIDA),
+    to_atom(ProfileID, ProfileIDA),
+    maplist(to_atom, Flags, Options),
+    notify_open_db,
+    (   follower(DocIDA, ProfileIDA, OldOptions)
+    ->  (   OldOptions == Options
+        ->  true
+        ;   retractall_follower(DocIDA, ProfileIDA, _),
+            (   Options \== []
+            ->  assert_follower(DocIDA, ProfileIDA, Options)
+            ;   true
+            )
+        )
+    ;   Options \== []
+    ->  assert_follower(DocIDA, ProfileIDA, Options)
+    ;   true
+    ).
+
+nofollow(DocID, ProfileID, Flags) :-
+    to_atom(DocID, DocIDA),
+    to_atom(ProfileID, ProfileIDA),
+    maplist(to_atom, Flags, Options),
+    (   follower(DocIDA, ProfileIDA, OldOptions)
+    ->  subtract(OldOptions, Options, NewOptions),
+        follow(DocID, ProfileID, NewOptions)
+    ;   true
+    ).
+
+
+%!  notify(+DocID, +Action) is det.
+%
+%   Action has been executed on DocID.  Notify all interested users.
+%   Actions that may be notified:
+%
+%   - updated(Commit)
+%     Gitty file was updated
+%   - deleted(Commit)
+%     Gitty file was deleted
+%   - forked(OldCommit, Commit)
+%     Gitty file was forked
+%   - chat(Message)
+%     A chat message was sent.  Message is the JSON content as a dict.
+%     Message contains a `docid` key.
+
+notify(DocID, Action) :-
+    to_atom(DocID, DocIDA),
+    try(notify_in_chat(DocIDA, Action)),
+    notify_open_db,
+    forall(follower(DocIDA, Profile, Options),
+           notify_user(Profile, DocIDA, Action, Options)).
+
+to_atom(Text, Atom) :-
+    atom_string(Atom, Text).
+
+%!  notify_user(+Profile, +DocID, +Action, +Options)
+%
+%   Notify the user belonging to Profile  about Action, which is related
+%   to document DocID.
+
+notify_user(Profile, _, Action, _Options) :-	% exclude self
+    event_generator(Action, Profile),
+    debug(notify(self), 'Notification to self ~p', [Profile]),
+    \+ debugging(notify_self),
+    !.
+notify_user(Profile, DocID, Action, Options) :-
+    try(notify_online(Profile, Action, Options)),
+    try(notify_by_mail(Profile, DocID, Action, Options)).
+
+try(Goal) :-
+    catch(Goal, Error, print_message(error, Error)),
+    !.
+try(_0Goal) :-
+    debug(notify(fail), 'Failed: ~p', [_0Goal]).
+
+
+		 /*******************************
+		 *         BROADCAST API	*
+		 *******************************/
+
+:- unlisten(swish(_)),
+   listen(swish(Event), notify_event(Event)).
+
+% request to follow this file
+notify_event(follow(DocID, ProfileID, Options)) :-
+    follow(DocID, ProfileID, Options).
+% events on gitty files
+notify_event(updated(File, Commit)) :-
+    atom_concat('gitty:', File, DocID),
+    notify(DocID, updated(Commit)).
+notify_event(deleted(File, Commit)) :-
+    atom_concat('gitty:', File, DocID),
+    notify(DocID, deleted(Commit)).
+notify_event(created(_File, Commit)) :-
+    storage_meta_data(Commit.get(previous), Meta),
+    atom_concat('gitty:', Meta.name, DocID),
+    notify(DocID, forked(Meta, Commit)).
+% chat message
+notify_event(chat(Message)) :-
+    notify(Message.docid, chat(Message)).
+
+%!  event_generator(+Event, -ProfileID) is semidet.
+%
+%   True when ProfileID refers to the user that initiated Event.
+
+event_generator(updated(Commit),   Commit.get(profile_id)).
+event_generator(deleted(Commit),   Commit.get(profile_id)).
+event_generator(forked(_, Commit), Commit.get(profile_id)).
+
+
+		 /*******************************
+		 *     NOTIFY PEOPLE ONLINE	*
+		 *******************************/
+
+notify_online(ProfileID, Action, _Options) :-
+    chat_to_profile(ProfileID, \short_notice(Action)).
+
+short_notice(updated(Commit)) -->
+    html([\committer(Commit), ' updated ', \file_name(Commit)]).
+short_notice(deleted(Commit)) -->
+    html([\committer(Commit), ' deleted ', \file_name(Commit)]).
+short_notice(forked(OldCommit, Commit)) -->
+    html([\committer(Commit), ' forked ', \file_name(OldCommit),
+          ' into ', \file_name(Commit)
+         ]).
+short_notice(chat(Message)) -->
+    html([\chat_user(Message), " chatted about ", \chat_file(Message)]).
+
+file_name(Commit) -->
+    { http_link_to_id(web_storage, path_postfix(Commit.name), HREF) },
+    html(a(href(HREF), Commit.name)).
+
+
+		 /*******************************
+		 *  ADD NOTIFICATIONS TO CHAT	*
+		 *******************************/
+
+%!  notify_in_chat(+DocID, +Action)
+
+:- html_meta(html_string(html, -)).
+
+notify_in_chat(_, chat(_)) :-
+    !.
+notify_in_chat(DocID, Action) :-
+    html_string(\chat_notice(Action, Payload), HTML),
+    action_user(Action, User),
+    Message0 = _{ type:"chat-message",
+                  class:"update",
+                  html:HTML,
+                  user:User,
+                  create:false
+                },
+    (   Payload == []
+    ->  Message = Message0
+    ;   Message = Message0.put(payload, Payload)
+    ),
+    chat_about(DocID, Message).
+
+
+html_string(HTML, String) :-
+    phrase(html(HTML), Tokens),
+    delete(Tokens, nl(_), SingleLine),
+    with_output_to(string(String), print_html(SingleLine)).
+
+
+chat_notice(updated(Commit), [_{type:update, name:Name,
+                                commit:CommitHash, previous:PrevCommit}]) -->
+    { _{name:Name, commit:CommitHash, previous:PrevCommit} :< Commit },
+    html([b('Saved'), ' new version: ', \commit_message_summary(Commit)]).
+chat_notice(deleted(Commit), []) -->
+    html([b('Deleted'), ': ', \commit_message_summary(Commit)]).
+chat_notice(forked(_OldCommit, Commit), []) -->
+    html([b('Forked'), ' into ', \file_name(Commit), ': ',
+          \commit_message_summary(Commit)
+         ]).
+
+commit_message_summary(Commit) -->
+    { Message = Commit.get(commit_message) }, !,
+    html(span(class(['commit-message']), Message)).
+commit_message_summary(_Commit) -->
+    html(span(class(['no-commit-message']), 'no message')).
+
+%!  action_user(+Action, -User) is det.
+%
+%   Describe a user for chat purposes.  Such a user is identified by the
+%   `profile_id`, `name` and/or `avatar`.
+
+action_user(Action, User) :-
+    action_commit(Action, Commit),
+    findall(Name-Value, commit_user_property(Commit, Name, Value), Pairs),
+    dict_pairs(User, u, Pairs).
+
+action_commit(forked(_From, Commit), Commit) :-
+    !.
+action_commit(Action, Commit) :-
+    arg(1, Action, Commit).
+
+commit_user_property(Commit, Name, Value) :-
+    Profile = Commit.get(profile_id),
+    !,
+    profile_user_property(Profile, Commit, Name, Value).
+commit_user_property(Commit, name, Name) :-
+    Name = Commit.get(author).
+commit_user_property(Commit, avatar, Avatar) :-
+    Avatar = Commit.get(avatar).
+
+profile_user_property(ProfileID, _,      profile_id, ProfileID).
+profile_user_property(_,         Commit, name,       Commit.get(author)).
+profile_user_property(ProfileID, Commit, avatar,     Avatar) :-
+    (   profile_property(ProfileID, avatar(Avatar))
+    ->  true
+    ;   Avatar = Commit.get(avatar)
+    ).
+
+
+		 /*******************************
+		 *            EMAIL		*
+		 *******************************/
+
+% ! notify_by_mail(+Profile, +DocID, +Action, +FollowOptions) is semidet.
+%
+%   Send a notification by mail. Optionally  schedules the message to be
+%   send later.
+%
+%   @tbd: if sending fails, should we queue the message?
+
+notify_by_mail(Profile, DocID, Action, Options) :-
+    profile_property(Profile, email(Email)),
+    profile_property(Profile, email_notifications(When)),
+    When \== never,
+    must_notify(Action, Options),
+    (   When == immediate
+    ->  debug(notify(email), 'Sending notification mail to ~p', [Profile]),
+        send_notification_mail(Profile, DocID, Email, Action)
+    ;   debug(notify(email), 'Queing notification mail to ~p', [Profile]),
+        queue_event(Profile, DocID, Action)
+    ).
+
+must_notify(chat(Message), Options) :- !,
+    memberchk(chat, Options),
+    \+ Message.get(class) == "update".
+must_notify(_, Options) :-
+    memberchk(update, Options).
+
+% ! send_notification_mail(+Profile, +DocID, +Email, +Action) is semidet.
+%
+%   Actually send a notification mail.  Fails   if  Profile  has no mail
+%   address or does not want to be notified by email.
+
+send_notification_mail(Profile, DocID, Email, Action) :-
+    phrase(subject(Action), Codes),
+    string_codes(Subject, Codes),
+    smtp_send_html(Email, \mail_message(Profile, DocID, Action),
+                   [ subject(Subject)
+                   ]).
+
+subject(Action) -->
+    subject_action(Action).
+
+subject_action(updated(Commit)) -->
+    txt_commit_file(Commit), " updated by ", txt_committer(Commit).
+subject_action(deleted(Commit)) -->
+    txt_commit_file(Commit), " deleted by ", txt_committer(Commit).
+subject_action(forked(_, Commit)) -->
+    txt_commit_file(Commit), " forked by ", txt_committer(Commit).
+subject_action(chat(Message)) -->
+    txt_chat_user(Message), " chatted about ", txt_chat_file(Message).
+
+
+		 /*******************************
+		 *             STYLE		*
+		 *******************************/
+
+style -->
+    email_style,
+    notify_style.
+
+notify_style -->
+    html({|html||
+<style>
+ .block            {margin-left: 2em;}
+p.commit-message,
+p.chat             {color: darkgreen;}
+p.nocommit-message {color: orange;}
+pre.query          {}
+div.query	   {margin-top:2em; border-top: 1px solid #888;}
+div.query-title	   {font-size: 80%; color: #888;}
+div.nofollow	   {margin-top:2em; border-top: 1px solid #888;
+                    font-size: 80%; color: #888; }
+</style>
+         |}).
+
+
+
+
+		 /*******************************
+		 *            HTML BODY		*
+		 *******************************/
+
+%!  message(+ProfileID, +DocID, +Action)//
+
+mail_message(ProfileID, DocID, Action) -->
+    dear(ProfileID),
+    notification(Action),
+    unsubscribe_options(ProfileID, DocID, Action),
+    signature,
+    style.
+
+notification(updated(Commit)) -->
+    html(p(['The file ', \global_commit_file(Commit),
+            ' has been updated by ', \committer(Commit), '.'])),
+    commit_message(Commit).
+notification(forked(OldCommit, Commit)) -->
+    html(p(['The file ', \global_commit_file(OldCommit),
+            ' has been forked into ', \global_commit_file(Commit), ' by ',
+            \committer(Commit), '.'])),
+    commit_message(Commit).
+notification(deleted(Commit)) -->
+    html(p(['The file ', \global_commit_file(Commit),
+            ' has been deleted by ', \committer(Commit), '.'])),
+    commit_message(Commit).
+notification(chat(Message)) -->
+    html(p([\chat_user(Message), " chatted about ", \chat_file(Message)])),
+    chat_message(Message).
+
+global_commit_file(Commit) -->
+    global_gitty_link(Commit.name).
+
+global_gitty_link(File) -->
+    { public_url(web_storage, path_postfix(File), HREF, []) },
+    html(a(href(HREF), File)).
+
+committer(Commit) -->
+    { ProfileID = Commit.get(profile_id) }, !,
+    profile_name(ProfileID).
+committer(Commit) -->
+    html(Commit.get(owner)).
+
+commit_message(Commit) -->
+    { Message = Commit.get(commit_message) }, !,
+    html(p(class(['commit-message', block]), Message)).
+commit_message(_Commit) -->
+    html(p(class(['no-commit-message', block]), 'No message')).
+
+chat_file(Message) -->
+    global_docid_link(Message.docid).
+
+global_docid_link(DocID) -->
+    { string_concat("gitty:", File, DocID)
+    },
+    global_gitty_link(File).
+
+chat_user(Message) -->
+    { User = Message.get(user).get(name) },
+    !,
+    html(User).
+chat_user(_Message) -->
+    html("Someone").
+
+chat_message(Message) -->
+    (chat_text(Message)                  -> [] ; []),
+    (chat_payloads(Message.get(payload)) -> [] ; []).
+
+chat_text(Message) -->
+    html(p(class([chat,block]), Message.get(text))).
+
+chat_payloads([]) --> [].
+chat_payloads([H|T]) --> chat_payload(H), chat_payloads(T).
+
+chat_payload(PayLoad) -->
+    { atom_string(Type, PayLoad.get(type)) },
+    chat_payload(Type, PayLoad),
+    !.
+chat_payload(_) --> [].
+
+chat_payload(query, PayLoad) -->
+    html(div(class(query),
+             [ div(class('query-title'), 'Query'),
+               pre(class([query, block]), PayLoad.get(query))
+             ])).
+chat_payload(about, PayLoad) -->
+    html(div(class(about),
+             [ 'About file ', \global_docid_link(PayLoad.get(docid)) ])).
+chat_payload(Type, _) -->
+    html(p(['Unknown payload of type ~q'-[Type]])).
+
+
+		 /*******************************
+		 *          UNSUBSCRIBE		*
+		 *******************************/
+
+unsubscribe_options(ProfileID, DocID, _) -->
+    html(div(class(nofollow),
+             [ 'Stop following ',
+               \nofollow_link(ProfileID, DocID, [chat]), '||',
+               \nofollow_link(ProfileID, DocID, [update]), '||',
+               \nofollow_link(ProfileID, DocID, [chat,update]),
+               ' about this document'
+             ])).
+
+nofollow_link(ProfileID, DocID, What) -->
+    email_action_link(\nofollow_link_label(What),
+                      nofollow_page(ProfileID, DocID, What),
+                      nofollow(ProfileID, DocID, What),
+                      []).
+
+nofollow_link_label([chat])         --> html(chats).
+nofollow_link_label([update])       --> html(updates).
+nofollow_link_label([chat, update]) --> html('all notifications').
+
+nofollow_done([chat])         --> html(chat).
+nofollow_done([update])       --> html(update).
+nofollow_done([chat, update]) --> html('any notifications').
+
+nofollow_page(ProfileID, DocID, What, _Request) :-
+    reply_html_page(
+        email_confirmation,
+        title('SWISH -- Stopped following'),
+        [ \email_style,
+          \dear(ProfileID),
+          p(['You will no longer receive ', \nofollow_done(What),
+             'notifications about ', \docid_link(DocID), '. ',
+             'You can reactivate following this document using the \c
+              File/Follow ... menu in SWISH.  You can specify whether \c
+              and when you like to receive email notifications from your \c
+              profile page.'
+            ]),
+          \signature
+        ]).
+
+docid_link(DocID) -->
+    { atom_concat('gitty:', File, DocID),
+      http_link_to_id(web_storage, path_postfix(File), HREF)
+    },
+    !,
+    html(a(href(HREF), File)).
+docid_link(DocID) -->
+    html(DocID).
+
+
+		 /*******************************
+		 *  TEXT RULES ON GITTY COMMITS	*
+		 *******************************/
+
+txt_commit_file(Commit) -->
+    write(Commit.name).
+
+txt_committer(Commit) -->
+    { ProfileID = Commit.get(profile_id) }, !,
+    txt_profile_name(ProfileID).
+txt_committer(Commit) -->
+    write(Commit.get(owner)), !.
+
+
+
+		 /*******************************
+		 *    RULES ON GITTY COMMITS	*
+		 *******************************/
+
+txt_profile_name(ProfileID) -->
+    { profile_property(ProfileID, name(Name)) },
+    write(Name).
+
+
+		 /*******************************
+		 *    RULES ON CHAT MESSAGES	*
+		 *******************************/
+
+txt_chat_user(Message) -->
+    { User = Message.get(user).get(name) },
+    !,
+    write(User).
+txt_chat_user(_Message) -->
+    "Someone".
+
+txt_chat_file(Message) -->
+    { string_concat("gitty:", File, Message.docid) },
+    !,
+    write(File).
+
+
+		 /*******************************
+		 *            BASICS		*
+		 *******************************/
+
+write(Term, Head, Tail) :-
+    format(codes(Head, Tail), '~w', [Term]).
+
+
+		 /*******************************
+		 *        HTTP HANDLING		*
+		 *******************************/
+
+:- http_handler(swish(follow/options), follow_file_options,
+                [ id(follow_file_options) ]).
+:- http_handler(swish(follow/save), save_follow_file,
+                [ id(save_follow_file) ]).
+
+%!  follow_file_options(+Request)
+%
+%   Edit the file following options for the current user.
+
+follow_file_options(Request) :-
+    http_parameters(Request,
+                    [ docid(DocID, [atom])
+                    ]),
+    http_in_session(_SessionID),
+    http_session_data(profile_id(ProfileID)), !,
+    (   profile_property(ProfileID, email_notifications(When))
+    ->  true
+    ;   existence_error(profile_property, email_notifications)
+    ),
+
+    (   follower(DocID, ProfileID, Follow)
+    ->  true
+    ;   Follow = []
+    ),
+
+    follow_file_widgets(DocID, When, Follow, Widgets),
+
+    reply_html_page(
+        title('Follow file options'),
+        \bt_form(Widgets,
+                 [ class('form-horizontal'),
+                   label_columns(sm-3)
+                 ])).
+follow_file_options(_Request) :-
+    reply_html_page(
+        title('Follow file options'),
+        [ p('You must be logged in to follow a file'),
+          \bt_form([ button_group(
+                         [ button(cancel, button,
+                                  [ type(danger),
+                                    data([dismiss(modal)])
+                                  ])
+                         ], [])
+                   ],
+                   [ class('form-horizontal'),
+                     label_columns(sm-3)
+                   ])
+        ]).
+
+:- multifile
+    user_profile:attribute/3.
+
+follow_file_widgets(DocID, When, Follow,
+    [ hidden(docid, DocID),
+      checkboxes(follow, [update,chat], [value(Follow)]),
+      select(email_notifications, NotificationOptions, [value(When)])
+    | Buttons
+    ]) :-
+    user_profile:attribute(email_notifications, oneof(NotificationOptions), _),
+    buttons(Buttons).
+
+buttons(
+    [ button_group(
+          [ button(save, submit,
+                   [ type(primary),
+                     data([action(SaveHREF)])
+                   ]),
+            button(cancel, button,
+                   [ type(danger),
+                     data([dismiss(modal)])
+                   ])
+          ],
+          [
+          ])
+    ]) :-
+    http_link_to_id(save_follow_file, [], SaveHREF).
+
+%!  save_follow_file(+Request)
+%
+%   Save the follow file options
+
+save_follow_file(Request) :-
+    http_read_json_dict(Request, Dict),
+    debug(profile(update), 'Got ~p', [Dict]),
+    http_in_session(_SessionID),
+    http_session_data(profile_id(ProfileID)),
+    debug(notify(options), 'Set follow options to ~p', [Dict]),
+    set_profile(ProfileID, email_notifications=Dict.get(email_notifications)),
+    follow(Dict.get(docid), ProfileID, Dict.get(follow)),
+    reply_json_dict(_{status:success}).
diff --git a/lib/swish/plugin/profile.pl b/lib/swish/plugin/profile.pl
new file mode 100644
index 0000000..8ed3262
--- /dev/null
+++ b/lib/swish/plugin/profile.pl
@@ -0,0 +1,598 @@
+/*  Part of SWISH
+
+    Author:        Jan Wielemaker
+    E-mail:        J.Wielemaker@cs.vu.nl
+    WWW:           http://www.swi-prolog.org
+    Copyright (C): 2017, VU University Amsterdam
+			 CWI Amsterdam
+    All rights reserved.
+
+    Redistribution and use in source and binary forms, with or without
+    modification, are permitted provided that the following conditions
+    are met:
+
+    1. Redistributions of source code must retain the above copyright
+       notice, this list of conditions and the following disclaimer.
+
+    2. Redistributions in binary form must reproduce the above copyright
+       notice, this list of conditions and the following disclaimer in
+       the documentation and/or other materials provided with the
+       distribution.
+
+    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
+    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
+    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
+    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
+    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
+    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
+    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
+    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
+    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
+    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
+    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
+    POSSIBILITY OF SUCH DAMAGE.
+*/
+
+:- module(swish_plugin_user_profile,
+          [
+          ]).
+:- use_module(library(option)).
+:- use_module(library(user_profile)).
+:- use_module(library(http/http_dispatch)).
+:- use_module(library(http/http_session)).
+:- use_module(library(http/http_wrapper)).
+:- use_module(library(http/html_write)).
+:- use_module(library(http/http_json)).
+:- use_module(library(apply)).
+:- use_module(library(error)).
+:- use_module(library(lists)).
+:- use_module(library(debug)).
+:- use_module(library(broadcast)).
+:- use_module(library(pairs)).
+
+:- use_module('../config', []).
+:- use_module(login).
+:- use_module('../authenticate').
+:- use_module('../bootstrap').
+:- use_module('../form').
+:- use_module('../avatar').
+
+
+/** <module> User profile configuration
+
+Complementary to authentication, this module  configures the maintenance
+of user profiles.
+
+There are several  places  where  we   need  interaction  with  the user
+profile:
+
+  - Prolog gathering and maintenance
+
+    1. If a new user is found we want to welcome the user and
+       optionally complete the profile.  For example, we may wish
+       to ask the `email` for the new user and start a process to
+       verify this.
+    2. A user must be able to edit and delete his/her profile.
+    3. A user must be able to migrate a profile, probably only from
+       a profile with the same verified email address.
+
+  - Profile usage
+
+    1. Claim ownership
+       - To files
+       - To comments
+    2. Grant access.  Access points in SWISH should be
+       - Execution of goals
+	 - Normal sandboxed/not-sandboxed operations
+         - Grant/Deny access to certain sensitive (database)
+           predicates.
+       - Viewing/using code
+       - Saving code
+         - Save in general (e.g., do not save when anonymous)
+         - Make revisions to files that are not yours
+         - Save non-versioned files
+         - Add modules to the version store?
+    3. Send notifications
+       - By mail
+       - Maintain notification queue for a user
+*/
+
+:- http_handler(swish(user_profile),   user_profile,   [id(user_profile)]).
+:- http_handler(swish(save_profile),   save_profile,   []).
+:- http_handler(swish(update_profile), update_profile, []).
+:- http_handler(swish(delete_profile), delete_profile, []).
+
+
+:- multifile
+    swish_config:reply_logged_in/1,     % +Options
+    swish_config:reply_logged_out/1,    % +Options
+    swish_config:user_profile/2.        % +Request, -Info
+
+
+		 /*******************************
+		 *            LOGIN		*
+		 *******************************/
+
+%!  swish_config:reply_logged_in(+Options)
+%
+%   Hook logins from federated identity provides.  Options processed:
+%
+%     - user_info(+UserInfo:Dict)
+%     Provides information about the user provided by the external
+%     identity provider.
+%     - reply(+Format)
+%     If Format = `html`, reply with an HTML page.  Other values
+%     are left for future extensions.
+%     - profile_id(-Id)
+%     Unify Id with the found or created profile id.
+
+swish_config:reply_logged_in(Options) :-
+    option(user_info(Info), Options),
+    known_profile(Info, ProfileID),
+    !,
+    option(profile_id(ProfileID), Options, _),
+    associate_profile(ProfileID),
+    (   option(reply(html), Options, html)
+    ->  reply_html_page(
+            title('Logged in'),
+            [ h4('Welcome back'),
+              p(\last_login(ProfileID)),
+              \login_continue_button
+            ])
+    ;   true
+    ).
+swish_config:reply_logged_in(Options) :-
+    option(user_info(Info), Options),
+    create_profile(Info, Info.get(identity_provider), ProfileID),
+    !,
+    option(profile_id(ProfileID), Options, _),
+    http_open_session(_SessionID, []),
+    associate_profile(ProfileID),
+    update_last_login(ProfileID),
+    (   option(reply(html), Options, html)
+    ->  reply_html_page(
+            title('Logged in'),
+            [ h4('Welcome'),
+              p([ 'You appear to be a new user.  You may inspect, update \c
+                  and delete your profile using the drop-down menu associated \c
+                  with the login/logout widget.'
+                ]),
+              \login_continue_button
+            ])
+    ;   true
+    ).
+
+%!  known_profile(+Info, -ProfileID) is semidet.
+%
+%   True when ProfileID is the profile  identifier for the authenticated
+%   user.
+
+known_profile(Info, ProfileID) :-
+    IdProvider = Info.get(identity_provider),
+    profile_default(IdProvider, Info, external_identity(ID)),
+    profile_property(ProfileID, external_identity(ID)),
+    profile_property(ProfileID, identity_provider(IdProvider)),
+    !.
+
+
+%!  associate_profile(+ProfileID) is det.
+%
+%   Associate the current session with   the given ProfileID. Broadcasts
+%   SWISH event profile(ProfileID).
+
+associate_profile(ProfileID) :-
+    http_session_assert(profile_id(ProfileID)),
+    broadcast(swish(profile(ProfileID))).
+
+
+%!  init_session_profile
+%
+%   This deals with the case where  a   session  is opened, but login is
+%   continued because it is based on HTTP authentication.  If the server
+%   opens a session, we check for the current identity and associate the
+%   related profile.
+
+:- listen(http_session(begin(_SessionID, _Peer)),
+          init_session_profile).
+
+init_session_profile :-
+    http_current_request(Request),
+    authenticate(Request, Identity),
+    known_profile(Request, Identity, ProfileID),
+    associate_profile(ProfileID).
+
+known_profile(_Request, Identity, ProfileID) :-
+    known_profile(Identity, ProfileID),
+    !.
+known_profile(Request, Identity, ProfileID) :-
+    local == Identity.get(identity_provider),
+    swish_config:user_info(Request, local, UserInfo),
+    create_profile(UserInfo, local, ProfileID).
+
+
+%!  swish_config:reply_logged_out(+Options)
+%
+%   Perform a logout, removing the link to the session
+
+swish_config:reply_logged_out(Options) :-
+    http_in_session(_),
+    !,
+    forall(http_session_retract(profile_id(ProfileID)),
+           broadcast(swish(logout(ProfileID)))),
+    reply_logged_out_page(Options).
+swish_config:reply_logged_out(_) :-
+    broadcast(swish(logout(-))).        % ?
+
+
+%!  create_profile(+UserInfo, +IDProvider, -ProfileID)
+%
+%   Create a new user profile.
+
+create_profile(UserInfo, IdProvider, ProfileID) :-
+    user_profile_values(UserInfo, IdProvider, Defaults),
+    profile_create(ProfileID, Defaults).
+
+user_profile_values(UserInfo, IdProvider, Defaults) :-
+    findall(Default,
+            profile_default(IdProvider, UserInfo, Default),
+            Defaults0),
+    add_gravatar(Defaults0, Defaults).
+
+profile_default(IdProvider, UserInfo, Default) :-
+    (   nonvar(Default)
+    ->  functor(Default, Name, 1)
+    ;   true
+    ),
+    user_profile:attribute(Name, _, _),
+    user_profile:attribute_mapping(Name, IdProvider, UName),
+    catch(profile_canonical_value(Name, UserInfo.get(UName), Value),
+          error(type_error(_,_),_),
+          fail),
+    Default =.. [Name,Value].
+profile_default(local, UserInfo, email_verified(true)) :-
+    _ = UserInfo.get(email).                    % trust our own user data
+
+add_gravatar(Defaults0, Defaults) :-
+    \+ memberchk(avatar(_), Defaults0),
+    memberchk(email(Email), Defaults0),
+    email_gravatar(Email, Avatar0),
+    valid_gravatar(Avatar0),
+    catch(profile_canonical_value(avatar, Avatar0, Avatar),
+          error(type_error(_,_),_),
+          fail),
+    !,
+    Defaults = [avatar(Avatar)|Defaults0].
+add_gravatar(Defaults, Defaults).
+
+
+%!  last_login(+User)//
+%
+%   Indicate when the user used this server for the last time.
+
+last_login(User) -->
+    { profile_property(User, last_login(TimeStamp)),
+      profile_property(User, last_peer(Peer)),
+      format_time(string(Time), '%+', TimeStamp),
+      update_last_login(User)
+    },
+    !,
+    html('Last login: ~w from ~w'-[Time, Peer]).
+last_login(User) -->
+    { update_last_login(User) }.
+
+update_last_login(User) :-
+    http_current_request(Request),
+    http_peer(Request, Peer),
+    get_time(Now),
+    NowInt is round(Now),
+    set_profile(User, last_peer(Peer)),
+    set_profile(User, last_login(NowInt)).
+
+%!  swish_config:user_profile(+Request, -Profile) is semidet.
+%
+%   Provide the profile for the current  user. The Profile dict contains
+%   the profile keys and the `profile_id` key.
+
+swish_config:user_profile(_Request, Profile) :-
+    http_in_session(_SessionID),
+    http_session_data(profile_id(User)),
+    current_profile(User, Profile0),
+    Profile = Profile0.put(profile_id, User).
+
+
+		 /*******************************
+		 *         PROFILE GUI		*
+		 *******************************/
+
+%!  user_profile(+Request)
+%
+%   Emit an HTML page that allows for   viewing, updating and deleting a
+%   user profile.
+
+user_profile(_Request) :-
+    http_in_session(_SessionID),
+    http_session_data(profile_id(User)), !,
+    current_profile(User, Profile),
+    findall(Field, user_profile:attribute(Field, _, _), Fields),
+    convlist(bt_field(Profile), Fields, FieldWidgets),
+    buttons(Buttons),
+    append(FieldWidgets, Buttons, Widgets),
+    reply_html_page(
+        title('User profile'),
+        \bt_form(Widgets,
+                 [ class('form-horizontal'),
+                   label_columns(sm-3)
+                 ])).
+user_profile(_Request) :-
+    reply_html_page(
+        title('User profile'),
+        [ p('You must be logged in to view your profile'),
+          \bt_form([ button_group(
+                         [ button(cancel, button,
+                                  [ type(danger),
+                                    data([dismiss(modal)])
+                                  ])
+                         ], [])
+                   ],
+                   [ class('form-horizontal'),
+                     label_columns(sm-3)
+                   ])
+        ]).
+
+
+bt_field(Profile, Name, Field) :-
+    user_profile:attribute(Name, Type, AOptions),
+    !,
+    \+ option(hidden(true), AOptions),
+    bt_field(Profile, Name, Type, AOptions, Field).
+
+bt_field(Profile, Name, Type, AOptions, select(Name, Values, Options)) :-
+    Type = oneof(Values),
+    !,
+    phrase(( (value_opt(Profile, Type, Name) -> [] ; []),
+             (access_opt(AOptions)           -> [] ; [])
+           ), Options).
+bt_field(Profile, Name, Type, AOptions, input(Name, IType, Options)) :-
+    input_type(Type, IType),
+    phrase(( (value_opt(Profile, Type, Name) -> [] ; []),
+             (access_opt(AOptions)           -> [] ; []),
+             (data_type_opt(Type)            -> [] ; [])
+           ), Options).
+
+input_type(boolean, checkbox) :-
+    !.
+input_type(_,       text).
+
+value_opt(Profile, Type, Name) -->
+    { Value0 = Profile.get(Name),
+      display_value(Type, Value0, Value)
+    },
+    [ value(Value) ].
+access_opt(AOptions) -->
+    { option(access(ro), AOptions) },
+    [ disabled(true) ].
+data_type_opt(_Type) -->                % TBD
+    [].
+
+display_value(time_stamp(Format), Stamp, Value) :-
+    !,
+    format_time(string(Value), Format, Stamp).
+display_value(_, Value0, Value) :-
+    atomic(Value0),
+    !,
+    Value = Value0.
+display_value(_, Value0, Value) :-
+    format(string(Value), '~w', [Value0]).
+
+buttons(
+    [ button_group(
+          [ button(done, button,
+                   [ type(primary),
+                     data([dismiss(modal)])
+                   ]),
+            button(save, submit,
+                   [ type(success),
+                     label('Save profile'),
+                     data([action(SaveHREF)])
+                   ]),
+            button(reset, submit,
+                   [ type(warning),
+                     label('Reset profile'),
+                     data([action(UpdateHREF), form_data(false)])
+                   ]),
+            button(delete, submit,
+                   [ type(danger),
+                     label('Delete profile'),
+                     data([action(DeleteHREF), form_data(false)])
+                   ])
+          ],
+          [
+          ])
+    ]) :-
+    http_link_to_id(save_profile, [], SaveHREF),
+    http_link_to_id(update_profile, [], UpdateHREF),
+    http_link_to_id(delete_profile, [], DeleteHREF).
+
+
+		 /*******************************
+		 *        MODIFY PROFILE	*
+		 *******************************/
+
+%!  save_profile(+Request)
+%
+%   Update the profile for the  current  user.   The  form  sends a JSON
+%   object that contains a value for all non-disabled fields that have a
+%   non-null value.
+
+save_profile(Request) :-
+    http_read_json_dict(Request, Dict),
+    debug(profile(update), 'Got ~p', [Dict]),
+    http_in_session(_SessionID),
+    http_session_data(profile_id(User)),
+    dict_pairs(Dict, _, Pairs),
+    maplist(validate_term, Pairs, VPairs, Validate),
+    catch(validate_form(Dict, Validate), E, true),
+    (   var(E)
+    ->  dict_pairs(VDict, _, VPairs),
+        save_profile(User, VDict),
+        current_profile(User, Profile),
+        reply_json_dict(_{status:success, profile:Profile})
+    ;   message_to_string(E, Msg),
+        Error = _{code:form_error, data:Msg},
+        reply_json_dict(_{status:error, error:Error})
+    ).
+
+validate_term(Name-_, Name-Value,
+              field(Name, Value, [strip,default("")|Options])) :-
+    user_profile:attribute(Name, Type, FieldOptions),
+    (   (   option(access(ro), FieldOptions)
+        ;   option(hidden(true), FieldOptions)
+        )
+    ->  permission_error(modify, profile, Name)
+    ;   true
+    ),
+    type_options(Type, Options).
+
+type_options(Type, [Type]).
+
+%!  save_profile(+User, +Dict) is det.
+%
+%   Update the profile for User with values from Dict.
+
+save_profile(User, Dict) :-
+    dict_pairs(Dict, _, Pairs),
+    maplist(save_profile_field(User), Pairs).
+
+save_profile_field(User, Name-Value) :-
+    (   Term =.. [Name,Old],
+        profile_property(User, Term)
+    ->  true
+    ;   Old = ""
+    ),
+    update_profile_field(User, Name, Old, Value).
+
+update_profile_field(User, Name, Old, "") :-
+    !,
+    profile_remove(User, Name),
+    broadcast(user_profile(modified(User, Name, Old, ""))).
+update_profile_field(User, Name, Old, New0) :-
+    profile_canonical_value(Name, New0, New),
+    (   Old == New
+    ->  true
+    ;   set_profile(User, Name=New),
+        broadcast(user_profile(modified(User, Name, Old, New)))
+    ).
+
+
+%!  update_profile(+Request)
+%
+%   Update a profile with new information from the identity provider
+
+update_profile(Request) :-
+    swish_config:user_info(Request, Server, UserInfo),
+    http_in_session(_SessionID),
+    http_session_data(profile_id(User)),
+    user_profile_values(UserInfo, Server, ServerInfo),
+    dict_pairs(ServerInfo, _, Pairs),
+    maplist(update_profile_field(User), Pairs),
+    current_profile(User, Profile),
+    reply_json_dict(_{status:success, profile:Profile}).
+
+update_profile_field(User, Name-Value) :-
+    set_profile(User, Name=Value).
+
+%!  delete_profile(+Request)
+%
+%   Completely delete the profile for the current user
+
+delete_profile(_Request) :-
+    http_in_session(SessionID),
+    http_session_data(profile_id(User)),
+    http_close_session(SessionID),      % effectively logout
+    profile_remove(User),
+    reply_json_dict(true).
+
+
+		 /*******************************
+		 *           PROPERTIES		*
+		 *******************************/
+
+:- listen(identity_property(Identity, Property),
+          from_profile(Identity, Property)).
+
+from_profile(Identity, Property) :-
+    profile_property(Identity.get(profile_id), Property).
+
+%!  profile_name(+ProfileID, -Name) is semidet.
+%
+%   Name is the public name associated with Profile.
+
+profile_name(ProfileID, Name) :-
+    user_field(Field),
+    Term =.. [Field, Name],
+    profile_property(ProfileID, Term),
+    !.
+
+user_field(name).
+user_field(given_name).
+user_field(nick_name).
+user_field(family_name).
+
+
+		 /*******************************
+		 *           TYPE AHEAD		*
+		 *******************************/
+
+:- multifile
+	swish_search:typeahead/4.	% +Set, +Query, -Match, +Options
+
+%!  swish_search:typeahead(+Set, +Query, -Match, +Options) is nondet.
+%
+%   Find users based on their  profile.   This  handler  defines the set
+%   `user`. A Match is a dict holding:
+%
+%     - id:ProfileID
+%     - label:Name
+%     A reasonable name for the user
+%     - email:Email
+%     Only present if the match was found on the email.
+%     - hit:hit{key:Key,value:Value}
+%     Field key and value on which the hit was found
+%     - avatar:Avatar
+%     Avatar URL
+
+swish_search:typeahead(user, Query, User, _Options) :-
+    current_profile(ProfileID, Attributes),
+    Keys = [name,given_name,family_name,email],
+    pairs_keys_values(Pairs, Keys, _),
+    dict_pairs(Profile, _, Pairs),
+    Profile >:< Attributes,
+    profile_match_query(Query, Pairs, Key),
+    user_dict(ProfileID, Key, Attributes, User).
+
+profile_match_query(Query, Pairs, Key) :-
+    member(Key-Value, Pairs),
+    text(Value),
+    sub_atom_icasechk(Value, 0, Query),
+    !.
+
+text(Value) :-
+    string(Value),
+    !.
+text(Value) :-
+    atom(Value).
+
+user_dict(ProfileID, SearchKey, Attributes, Dict) :-
+    findall(Key-Value,
+            user_search_property(ProfileID,SearchKey,Attributes,Key,Value),
+            Pairs),
+    dict_pairs(Dict, user, Pairs).
+
+user_search_property(ProfileID, _, _, id,    ProfileID).
+user_search_property(ProfileID, _, _, name,  Name) :-
+    profile_name(ProfileID, Name).
+user_search_property(_, email,  Attrs, email,  Attrs.get(email)).
+user_search_property(_, Search, Attrs, hit,    hit{key:Search,
+                                                   value:Attrs.get(Search)}).
+user_search_property(_, _,      Attrs, avatar, Attrs.get(avatar)).
+
diff --git a/lib/swish/render/graphviz.pl b/lib/swish/render/graphviz.pl
index 31dcdf1..8f7d404 100644
--- a/lib/swish/render/graphviz.pl
+++ b/lib/swish/render/graphviz.pl
@@ -147,7 +147,7 @@ render_dot(DOTString, Program, _Options) -->	% <svg> rendering
 	  call_cleanup((   read_string(XDotOut, _, SVG),
 			   read_string(ErrorOut, _, Error)
 		       ),
-		       (   process_wait(PID, _Status),
+		       (   process_wait_0(PID),
 			   close(ErrorOut, [force(true)]),
 			   close(XDotOut)
 		       ))
@@ -161,6 +161,13 @@ render_dot(DOTString, Program, _Options) -->	% <svg> rendering
 		     [ '~w'-[Program], ': ', Error]))
 	).
 
+process_wait_0(PID) :-
+	process_wait(PID, Status),
+	(   Status == exit(0)
+	->  true
+	;   print_message(error, format('Process ~q died on ~q', [PID, Status]))
+	).
+
 %%	svg(+SVG:string, +Options:list)//
 %
 %	Include SVG as pan/zoom image. Must be  embedded in a <div> with
@@ -205,6 +212,7 @@ svg(SVG, _Options) -->
        updateSize()
        pan = svgPanZoom(svg[0], {
 			  // controlIconsEnabled: true
+			  minZoom: 0.1,
 			  maxZoom: 50
 			});
     });
@@ -244,6 +252,8 @@ graphviz_program(fdp).
 graphviz_program(sfdp).
 graphviz_program(twopi).
 graphviz_program(circo).
+graphviz_program(osage).
+graphviz_program(patchwork).
 
 graph_type(graph).
 graph_type(digraph).
@@ -265,7 +275,7 @@ swish_send_graphviz(Request) :-
 				      [ dialect(xml) ]),
 		       read_string(ErrorOut, _, Error)
 		     ),
-		     (	 process_wait(PID, _Status),
+		     (	 process_wait_0(PID),
 			 close(ErrorOut, [force(true)]),
 			 close(XDotOut)
 		     )),
@@ -273,7 +283,7 @@ swish_send_graphviz(Request) :-
 	->  true
 	;   print_message(error, format('~w', [Error]))
 	),
-	rewrite_sgv_dom(SVGDom0, SVGDom),
+	rewrite_svg_dom(SVGDom0, SVGDom),
 	format('Content-type: ~w~n~n', ['image/svg+xml; charset=UTF-8']),
 	xml_write(current_output, SVGDom,
 		  [ layout(false)
@@ -292,7 +302,7 @@ graphviz_stream(Data, PID, XDotOut, Error) :-
 		      [ detached(true) ]).
 
 
-rewrite_sgv_dom([element(svg, Attrs, Content)],
+rewrite_svg_dom([element(svg, Attrs, Content)],
 		[element(svg, Attrs,
 			 [ element(script, ['xlink:href'=SVGPan], []),
 			   element(g, [ id=viewport
@@ -300,7 +310,7 @@ rewrite_sgv_dom([element(svg, Attrs, Content)],
 				   Content)
 			 ])]) :-
 	http_absolute_location(js('SVGPan.js'), SVGPan, []).
-rewrite_sgv_dom(DOM, DOM).
+rewrite_svg_dom(DOM, DOM).
 
 send_to_dot(Data, Out) :-
 	call_cleanup(format(Out, '~s', [Data]),
diff --git a/lib/swish/render/table.pl b/lib/swish/render/table.pl
index 5431311..6e111ca 100644
--- a/lib/swish/render/table.pl
+++ b/lib/swish/render/table.pl
@@ -62,14 +62,15 @@ Render table-like data.
 %	@tbd: recognise more formats
 
 term_rendering(Term, _Vars, Options) -->
-	{ is_list_of_dicts(Term, _Rows, ColNames)
+	{ is_list_of_dicts(Term, _Rows, ColNames), !,
+	  partition(is_header, Options, _HeaderOptions, Options1)
 	}, !,
 	html(div([ style('display:inline-block'),
 		   'data-render'('List of terms as a table')
 		 ],
 		 [ table(class('render-table'),
 			 [ \header_row(ColNames),
-			   \rows(Term, Options)
+			   \rows(Term, Options1)
 			 ])
 		 ])).
 term_rendering(Term, _Vars, Options) -->
diff --git a/lib/swish/search.pl b/lib/swish/search.pl
index 7cbbc96..297f690 100644
--- a/lib/swish/search.pl
+++ b/lib/swish/search.pl
@@ -3,7 +3,7 @@
     Author:        Jan Wielemaker
     E-mail:        J.Wielemaker@vu.nl
     WWW:           http://www.swi-prolog.org
-    Copyright (c)  2015-2016, VU University Amsterdam
+    Copyright (c)  2015-2017, VU University Amsterdam
     All rights reserved.
 
     Redistribution and use in source and binary forms, with or without
@@ -73,7 +73,7 @@ search_box(_Options) -->
 	html(form([class('navbar-form'), role(search)],
 		  div(class('input-group'),
 		      [ input([ type(text),
-				class('form-control'),
+				class(['form-control', typeahead]),
 				placeholder('Search'),
 				'data-search-in'([source,files,predicates]),
 				title('Searches code, documentation and files'),
diff --git a/lib/swish/storage.pl b/lib/swish/storage.pl
index 549ede2..bf09f21 100644
--- a/lib/swish/storage.pl
+++ b/lib/swish/storage.pl
@@ -3,7 +3,7 @@
     Author:        Jan Wielemaker
     E-mail:        J.Wielemaker@vu.nl
     WWW:           http://www.swi-prolog.org
-    Copyright (c)  2014-2016, VU University Amsterdam
+    Copyright (c)  2014-2017, VU University Amsterdam
     All rights reserved.
 
     Redistribution and use in source and binary forms, with or without
@@ -34,12 +34,13 @@
 
 :- module(web_storage,
 	  [ storage_file/1,			% ?File
-	    storage_file/3			% +File, -Data, -Meta
+	    storage_file/3,			% +File, -Data, -Meta
+	    storage_meta_data/2,		% +File, -Meta
+	    storage_meta_property/2	        % +Meta, ?Property
 	  ]).
 :- use_module(library(http/http_dispatch)).
 :- use_module(library(http/http_parameters)).
 :- use_module(library(http/http_json)).
-:- use_module(library(http/http_wrapper)).
 :- use_module(library(http/mimetype)).
 :- use_module(library(lists)).
 :- use_module(library(settings)).
@@ -47,6 +48,8 @@
 :- use_module(library(apply)).
 :- use_module(library(option)).
 :- use_module(library(debug)).
+:- use_module(library(broadcast)).
+:- use_module(library(readutil)).
 :- use_module(library(solution_sequences)).
 
 :- use_module(page).
@@ -54,6 +57,8 @@
 :- use_module(patch).
 :- use_module(config).
 :- use_module(search).
+:- use_module(authenticate).
+:- use_module(pep).
 
 /** <module> Store files on behalve of web clients
 
@@ -63,19 +68,45 @@ notion of a _tree_. I.e., all files   are considered individual and have
 their own version.
 */
 
-:- setting(directory, atom, storage, 'The directory for storing files.').
+:- setting(directory, callable, data(storage),
+	   'The directory for storing files.').
 
 :- http_handler(swish('p/'), web_storage, [ id(web_storage), prefix ]).
 
-:- initialization open_gittystore.
+:- initialization open_gittystore.		% TBD: make this lazy?
+
+:- dynamic  storage_dir/1.
+:- volatile storage_dir/1.
 
 open_gittystore :-
-	setting(directory, Dir),
-	(   exists_directory(Dir)
-	->  true
-	;   make_directory(Dir)
-	),
-	gitty_open(Dir, []).
+	storage_dir(_), !.
+open_gittystore :-
+	setting(directory, Spec),
+	absolute_file_name(Spec, Dir,
+			   [ file_type(directory),
+			     access(write),
+			     file_errors(fail)
+			   ]), !,
+	gitty_open(Dir, []),
+	asserta(storage_dir(Dir)).
+open_gittystore :-
+	setting(directory, Spec),
+	absolute_file_name(Spec, Dir,
+			   [ solutions(all)
+			   ]),
+	\+ exists_directory(Dir),
+	create_store(Dir), !,
+	gitty_open(Dir, []),
+	asserta(storage_dir(Dir)).
+
+create_store(Dir) :-
+	exists_directory('storage/ref'), !,
+	print_message(informational, moved_old_store(storage, Dir)),
+	rename_file(storage, Dir).
+create_store(Dir) :-
+	catch(make_directory(Dir),
+	      error(permission_error(create, directory, Dir), _),
+	      fail), !.
 
 
 %%	web_storage(+Request) is det.
@@ -86,17 +117,16 @@ open_gittystore :-
 %	methods =GET=, =POST=, =PUT= and =DELETE=.
 
 web_storage(Request) :-
+	authenticate(Request, Auth),
 	option(method(Method), Request),
-	storage(Method, Request).
+	storage(Method, Request, [identity(Auth)]).
 
 :- multifile
-	swish_config:authenticate/2.
+	swish_config:authenticate/2,
+	swish_config:chat_count_about/2,
+	swish_config:user_profile/2.		% +Request, -Profile
 
-storage(get, Request) :-
-	(   swish_config:authenticate(Request, User)
-	->  Options = [user(User)]
-	;   Options = []
-	),
+storage(get, Request, Options) :-
 	http_parameters(Request,
 			[ format(Fmt,  [ oneof([swish,raw,json,history,diff]),
 					 default(swish),
@@ -121,16 +151,16 @@ storage(get, Request) :-
 	),
 	storage_get(Request, Format, Options).
 
-storage(post, Request) :-
+storage(post, Request, Options) :-
 	http_read_json_dict(Request, Dict),
 	option(data(Data), Dict, ""),
 	option(type(Type), Dict, pl),
-	setting(directory, Dir),
-	make_directory_path(Dir),
-	meta_data(Request, Dir, Dict, Meta),
+	storage_dir(Dir),
+	meta_data(Dir, Dict, _, Meta, Options),
 	(   atom_string(Base, Dict.get(meta).get(name))
 	->  file_name_extension(Base, Type, File),
-	    (	catch(gitty_create(Dir, File, Data, Meta, Commit),
+	    (	authorized(gitty(create(File,named,Meta)), Options),
+		catch(gitty_create(Dir, File, Data, Meta, Commit),
 		      error(gitty(file_exists(File)),_),
 		      fail)
 	    ->	true
@@ -140,6 +170,7 @@ storage(post, Request) :-
 	;   (   repeat,
 	        random_filename(Base),
 		file_name_extension(Base, Type, File),
+		authorized(gitty(create(File,random,Meta)), Options),
 		catch(gitty_create(Dir, File, Data, Meta, Commit),
 		      error(gitty(file_exists(File)),_),
 		      fail)
@@ -150,38 +181,45 @@ storage(post, Request) :-
 	->  debug(storage, 'Created: ~p', [Commit]),
 	    storage_url(File, URL),
 
+	    broadcast(swish(created(File, Commit))),
+	    follow(Commit, Dict),
 	    reply_json_dict(json{url:URL,
 				 file:File,
 				 meta:Commit.put(symbolic, "HEAD")
 				})
 	;   reply_json_dict(Error)
 	).
-storage(put, Request) :-
+storage(put, Request, Options) :-
 	http_read_json_dict(Request, Dict),
-	setting(directory, Dir),
+	storage_dir(Dir),
 	request_file(Request, Dir, File),
 	(   Dict.get(update) == "meta-data"
 	->  gitty_data(Dir, File, Data, _OldMeta)
 	;   option(data(Data), Dict, "")
 	),
-	meta_data(Request, Dir, Dict, Meta),
+	meta_data(Dir, Dict, PrevMeta, Meta, Options),
 	storage_url(File, URL),
+	authorized(gitty(update(File,PrevMeta,Meta)), Options),
 	catch(gitty_update(Dir, File, Data, Meta, Commit),
 	      Error,
 	      true),
 	(   var(Error)
 	->  debug(storage, 'Updated: ~p', [Commit]),
-	    reply_json_dict(json{url:URL,
-				 file:File,
-				 meta:Commit.put(symbolic, "HEAD")
-			    })
+	    broadcast(swish(updated(File, Commit))),
+	    follow(Commit, Dict),
+	    reply_json_dict(json{ url:URL,
+				  file:File,
+				  meta:Commit.put(symbolic, "HEAD")
+				})
 	;   update_error(Error, Dir, Data, File, URL)
 	).
-storage(delete, Request) :-
-	authentity(Request, Meta),
-	setting(directory, Dir),
+storage(delete, Request, Options) :-
+	storage_dir(Dir),
+	meta_data(Dir, _{}, PrevMeta, Meta, Options),
 	request_file(Request, Dir, File),
-	gitty_update(Dir, File, "", Meta, _New),
+	authorized(gitty(delete(File,PrevMeta)), Options),
+	gitty_update(Dir, File, "", Meta, Commit),
+	broadcast(swish(deleted(File, Commit))),
 	reply_json_dict(true).
 
 %%	update_error(+Error, +Storage, +Data, +File, +URL)
@@ -216,6 +254,23 @@ patch_status(status(killed(Signal)), Dict, Dict.put(patch_killed, Signal)) :- !.
 patch_status(stderr(""), Dict, Dict) :- !.
 patch_status(stderr(Errors), Dict, Dict.put(patch_errors, Errors)) :- !.
 
+%!	follow(+Commit, +SaveDict) is det.
+%
+%	Broadcast follow(DocID, ProfileID, [update,chat])   if  the user
+%	wishes to follow the file associated with Commit.
+
+follow(Commit, Dict) :-
+	Dict.get(meta).get(follow) == true,
+	_{name:File, profile_id:ProfileID} :< Commit, !,
+	atom_concat('gitty:', File, DocID),
+	broadcast(swish(follow(DocID, ProfileID, [update,chat]))).
+follow(_, _).
+
+%!	request_file(+Request, +GittyDir, -File) is det.
+%
+%	Extract the gitty file referenced from the HTTP Request.
+%
+%	@error HTTP 404 exception
 
 request_file(Request, Dir, File) :-
 	option(path_info(File), Request),
@@ -227,50 +282,80 @@ request_file(Request, Dir, File) :-
 storage_url(File, HREF) :-
 	http_link_to_id(web_storage, path_postfix(File), HREF).
 
-%%	meta_data(+Request, +Dict, -Meta) is det.
-%%	meta_data(+Request, +Store, +Dict, -Meta) is det.
+%%	meta_data(+Dict, -Meta, +Options) is det.
+%%	meta_data(+Store, +Dict, -PrevMeta, -Meta, +Options) is det.
+%
+%	Gather meta-data from the  Request   (user,  peer, identity) and
+%	provided meta-data. Illegal and unknown values are ignored.
+%
+%	The meta_data/5 version is used to add information about a fork.
 %
-%	Gather meta-data from the  Request   (user,  peer)  and provided
-%	meta-data. Illegal and unknown values are ignored.
-
-meta_data(Request, Dict, Meta) :-
-	authentity(Request, Meta0),	% user, peer
-	(   filter_meta(Dict.get(meta), Meta1)
-	->  Meta = Meta0.put(Meta1)
-	;   Meta = Meta0
+%	@param Dict represents the JSON document posted and contains the
+%	content (`data`) and meta data (`meta`).
+
+meta_data(Dict, Meta, Options) :-
+	option(identity(Auth), Options),
+	(   _ = Auth.get(identity)
+	->  HasIdentity = true
+	;   HasIdentity = false
+	),
+	filter_auth(Auth, Auth1),
+	(   filter_meta(Dict.get(meta), HasIdentity, Meta1)
+	->  Meta = meta{}.put(Auth1).put(Meta1)
+	;   Meta = meta{}.put(Auth1)
 	).
 
-meta_data(Request, Store, Dict, Meta) :-
-	meta_data(Request, Dict, Meta1),
+meta_data(Store, Dict, PrevMeta, Meta, Options) :-
+	meta_data(Dict, Meta1, Options),
 	(   atom_string(Previous, Dict.get(previous)),
-	    is_sha1(Previous),
-	    gitty_commit(Store, Previous, _PrevMeta)
+	    is_gitty_hash(Previous),
+	    gitty_commit(Store, Previous, PrevMeta)
 	->  Meta = Meta1.put(previous, Previous)
 	;   Meta = Meta1
 	).
 
-filter_meta(Dict0, Dict) :-
+filter_meta(Dict0, HasID, Dict) :-
 	dict_pairs(Dict0, Tag, Pairs0),
-	filter_pairs(Pairs0, Pairs),
+	filter_pairs(Pairs0, HasID, Pairs),
 	dict_pairs(Dict, Tag, Pairs).
 
-filter_pairs([], []).
-filter_pairs([H|T0], [H|T]) :-
-	H = K-V,
-	meta_allowed(K, Type),
-	is_of_type(Type, V), !,
-	filter_pairs(T0, T).
-filter_pairs([_|T0], T) :-
-	filter_pairs(T0, T).
-
-meta_allowed(public,	     boolean).
-meta_allowed(example,	     boolean).
-meta_allowed(author,	     string).
-meta_allowed(email,	     string).
-meta_allowed(title,	     string).
-meta_allowed(tags,	     list(string)).
-meta_allowed(description,    string).
-meta_allowed(commit_message, string).
+filter_pairs([], _, []).
+filter_pairs([K-V0|T0], HasID, [K-V|T]) :-
+	meta_allowed(K, HasID, Type),
+	filter_type(Type, V0, V), !,
+	filter_pairs(T0, HasID, T).
+filter_pairs([_|T0], HasID, T) :-
+	filter_pairs(T0, HasID, T).
+
+meta_allowed(public,	     _,	    boolean).
+meta_allowed(example,	     _,	    boolean).
+meta_allowed(author,	     _,	    string).
+meta_allowed(avatar,	     false, string).
+meta_allowed(email,	     _,	    string).
+meta_allowed(title,	     _,	    string).
+meta_allowed(tags,	     _,	    list(string)).
+meta_allowed(description,    _,	    string).
+meta_allowed(commit_message, _,	    string).
+meta_allowed(modify,	     _,	    list(atom)).
+
+filter_type(Type, V, V) :-
+	is_of_type(Type, V), !.
+filter_type(list(Type), V0, V) :-
+	is_list(V0),
+	maplist(filter_type(Type), V0, V).
+filter_type(atom, V0, V) :-
+	atomic(V0),
+	atom_string(V, V0).
+
+filter_auth(Auth0, Auth) :-
+	auth_template(Auth),
+	Auth :< Auth0, !.
+filter_auth(Auth, Auth).
+
+auth_template(_{identity:_, profile_id:_}).
+auth_template(_{profile_id:_}).
+auth_template(_{identity:_}).
+
 
 %%	storage_get(+Request, +Format, +Options) is det.
 %
@@ -292,23 +377,33 @@ meta_allowed(commit_message, string).
 
 storage_get(Request, swish, Options) :-
 	swish_reply_config(Request, Options), !.
-storage_get(Request, Format, _) :-
-	setting(directory, Dir),
+storage_get(Request, Format, Options) :-
+	storage_dir(Dir),
 	request_file_or_hash(Request, Dir, FileOrHash, Type),
-	storage_get(Format, Dir, Type, FileOrHash, Request).
-
-storage_get(swish, Dir, _, FileOrHash, Request) :-
-	gitty_data(Dir, FileOrHash, Code, Meta),
-	swish_reply([code(Code),file(FileOrHash),st_type(gitty),meta(Meta)],
+	Obj =.. [Type,FileOrHash],
+	authorized(gitty(download(Obj, Format)), Options),
+	storage_get(Format, Dir, Type, FileOrHash, Request),
+	broadcast(swish(download(Dir, FileOrHash, Format))).
+
+storage_get(swish, Dir, Type, FileOrHash, Request) :-
+	gitty_data_or_default(Dir, Type, FileOrHash, Code, Meta),
+	chat_count(Meta, Count),
+	swish_reply([ code(Code),
+		      file(FileOrHash),
+		      st_type(gitty),
+		      meta(Meta),
+		      chat_count(Count)
+		    ],
 		    Request).
-storage_get(raw, Dir, _, FileOrHash, _Request) :-
-	gitty_data(Dir, FileOrHash, Code, Meta),
+storage_get(raw, Dir, Type, FileOrHash, _Request) :-
+	gitty_data_or_default(Dir, Type, FileOrHash, Code, Meta),
 	file_mime_type(Meta.name, MIME),
 	format('Content-type: ~w~n~n', [MIME]),
 	format('~s', [Code]).
-storage_get(json, Dir, _, FileOrHash, _Request) :-
-	gitty_data(Dir, FileOrHash, Code, Meta),
-	reply_json_dict(json{data:Code, meta:Meta}).
+storage_get(json, Dir, Type, FileOrHash, _Request) :-
+	gitty_data_or_default(Dir, Type, FileOrHash, Code, Meta),
+	chat_count(Meta, Count),
+	reply_json_dict(json{data:Code, meta:Meta, chats:_{count:Count}}).
 storage_get(history(Depth, Includes), Dir, _, File, _Request) :-
 	gitty_history(Dir, File, History, [depth(Depth),includes(Includes)]),
 	reply_json_dict(History).
@@ -323,43 +418,50 @@ request_file_or_hash(Request, Dir, FileOrHash, Type) :-
 	option(path_info(FileOrHash), Request),
 	(   gitty_file(Dir, FileOrHash, _Hash)
 	->  Type = file
-	;   is_sha1(FileOrHash)
+	;   is_gitty_hash(FileOrHash)
 	->  Type = hash
+	;   gitty_default_file(FileOrHash, _)
+	->  Type = default
 	;   http_404([], Request)
 	).
 
-is_sha1(SHA1) :-
-	atom_length(SHA1, 40),
-	atom_codes(SHA1, Codes),
-	maplist(hex_digit, Codes).
-
-hex_digit(C) :- between(0'0, 0'9, C), !.
-hex_digit(C) :- between(0'a, 0'f, C).
-
-%%	authentity(+Request, -Authentity:dict) is det.
+%!	gitty_data_or_default(+Dir, +Type, +FileOrHash, -Code, -Meta)
 %
-%	Provide authentication meta-information.  Currently user by
-%	exploiting the pengine authentication hook and peer.
-
-authentity(Request, Authentity) :-
-	phrase(authentity(Request), Pairs),
-	dict_pairs(Authentity, _, Pairs).
-
-authentity(Request) -->
-	(user(Request)->[];[]),
-	(peer(Request)->[];[]).
+%	Read a file from the gitty store. I   the file is not present, a
+%	default may be provided =gitty/File= in the config directory.
+
+gitty_data_or_default(_, default, File, Code,
+		      meta{name:File,
+			   modify:[login,owner],
+			   default:true,
+			   chat:"large"
+			  }) :- !,
+	gitty_default_file(File, Path),
+	read_file_to_string(Path, Code, []).
+gitty_data_or_default(Dir, _, FileOrHash, Code, Meta) :-
+	gitty_data(Dir, FileOrHash, Code, Meta), !.
+
+gitty_default_file(File, Path) :-
+	file_name_extension(Base, Ext, File),
+	memberchk(Ext, [pl,swinb]),
+	forall(sub_atom(Base, _, 1, _, C),
+	       char_type(C, csym)),
+	absolute_file_name(config(gitty/File), Path,
+			   [ access(read),
+			     file_errors(fail)
+			   ]).
+
+
+%!	chat_count(+Meta, -ChatCount) is det.
+%
+%	True when ChatCount is the number of chat messages available
+%	about Meta.
 
-:- multifile
-	pengines:authentication_hook/3.
+chat_count(Meta, Chats) :-
+	atom_concat('gitty:', Meta.get(name), DocID),
+	swish_config:chat_count_about(DocID, Chats), !.
+chat_count(_, 0).
 
-user(Request) -->
-	{ pengines:authentication_hook(Request, swish, User),
-	  ground(User)
-	},
-	[ user-User ].
-peer(Request) -->
-	{ http_peer(Request, Peer) },
-	[ peer-Peer ].
 
 %%	random_filename(-Name) is det.
 %
@@ -385,18 +487,58 @@ random_char(Char) :-
 		 *******************************/
 
 %%	storage_file(?File) is semidet.
-%%	storage_file(?File, -Data, -Meta) is semidet.
+%%	storage_file(+File, -Data, -Meta) is semidet.
+%%	storage_meta_data(+File, -Meta) is semidet.
 %
 %	True if File is known in the store.
+%
+%	@arg Data is a string holding the content of the file
+%	@arg Meta is a dict holding the meta data about the file.
 
 storage_file(File) :-
-	setting(directory, Dir),
+	storage_dir(Dir),
 	gitty_file(Dir, File, _Head).
 
 storage_file(File, Data, Meta) :-
-	setting(directory, Dir),
+	storage_dir(Dir),
 	gitty_data(Dir, File, Data, Meta).
 
+storage_meta_data(File, Meta) :-
+	storage_dir(Dir),
+	(   var(File)
+	->  gitty_file(Dir, File, _Head)
+	;   true
+	),
+	gitty_commit(Dir, File, Meta).
+
+%!	storage_meta_property(+Meta, -Property)
+%
+%	True when Meta has Property. Defined properties are:
+%
+%	  - peer(Atom)
+%	  Peer address that last saved the file
+%	  -
+
+storage_meta_property(Meta, Property) :-
+	current_meta_property(Property, How),
+	meta_property(Property, How, Meta).
+
+meta_property(Property, dict, Identity) :-
+	Property =.. [Name,Value],
+	Value = Identity.get(Name).
+meta_property(modify(Modify), _, Meta) :-
+	(   Modify0 = Meta.get(modify)
+	->  Modify = Modify0
+	;   Modify = [any,login,owner]
+	).
+
+current_meta_property(peer(_Atom),     dict).
+current_meta_property(public(_Bool),   dict).
+current_meta_property(time(_Seconds),  dict).
+current_meta_property(author(_String), dict).
+current_meta_property(avatar(_String), dict).
+current_meta_property(modify(_List),   derived).
+
 
 		 /*******************************
 		 *	 SEARCH SUPPORT		*
@@ -405,7 +547,7 @@ storage_file(File, Data, Meta) :-
 :- multifile
 	swish_search:typeahead/4.	% +Set, +Query, -Match, +Options
 
-%%	swish_search:typeahead(+Set, +Query, -Match) is nondet.
+%%	swish_search:typeahead(+Set, +Query, -Match, +Options) is nondet.
 %
 %	Find files using typeahead  from  the   SWISH  search  box. This
 %	version defines the following sets:
@@ -419,7 +561,7 @@ storage_file(File, Data, Meta) :-
 %	@tbd We should only demand public on public servers.
 
 swish_search:typeahead(file, Query, FileInfo, _Options) :-
-	setting(directory, Dir),
+	storage_dir(Dir),
 	gitty_file(Dir, File, Head),
 	gitty_commit(Dir, Head, Meta),
 	Meta.get(public) == true,
@@ -449,7 +591,7 @@ swish_search:typeahead(store_content, Query, FileInfo, Options) :-
 	limit(25, search_store_content(Query, FileInfo, Options)).
 
 search_store_content(Query, FileInfo, Options) :-
-	setting(directory, Dir),
+	storage_dir(Dir),
 	gitty_file(Dir, File, Head),
 	gitty_data(Dir, Head, Data, Meta),
 	Meta.get(public) == true,
@@ -462,3 +604,12 @@ search_file(File, Meta, Data, Query, FileInfo, Options) :-
 	FileInfo = Meta.put(_{type:"store", file:File,
 			      line:LineNo, text:Line, query:Query
 			     }).
+
+		 /*******************************
+		 *	      MESSAGES		*
+		 *******************************/
+
+:- multifile prolog:message//1.
+
+prolog:message(moved_old_store(Old, New)) -->
+	[ 'Moving SWISH file store from ~p to ~p'-[Old, New] ].
diff --git a/lib/swish/swish_csv.pl b/lib/swish/swish_csv.pl
index 5b5eaa4..89ca341 100644
--- a/lib/swish/swish_csv.pl
+++ b/lib/swish/swish_csv.pl
@@ -52,7 +52,6 @@ SWISH program and obtain the results using   a simple web client such as
 
 :- multifile
 	pengines:write_result/3,
-	pengines:write_result/4,
 	write_answers/2,		% Answers, Bindings
 	write_answers/3.		% Answers, Bindings, Options
 
@@ -61,38 +60,35 @@ SWISH program and obtain the results using   a simple web client such as
 %	Hook into library(pengines) that  makes   pengines  support  CSV
 %	output.
 
-pengines:write_result(csv, Event, VarNames) :-
-	csv(Event, VarNames, []).
-pengines:write_result(csv, Event, VarNames, OptionDict) :-
+pengines:write_result(csv, Event, OptionDict) :-
 	(   Disposition = OptionDict.get(disposition)
 	->  Options = [disposition(Disposition)]
 	;   Options = []
 	),
-	csv(Event, VarNames, Options).
+	csv(Event, Options).
 
-csv(create(_Id, Features), VarNames, Options) :- !,
+csv(create(_Id, Features), Options) :- !,
 	memberchk(answer(Answer), Features),
-	csv(Answer, VarNames, Options).
-csv(destroy(_Id, Wrapped), VarNames, Options) :- !,
-	csv(Wrapped, VarNames, Options).
-csv(success(_Id, Answers, _Time, More), VarNames, Options) :- !,
-	VarTerm =.. [row|VarNames],
+	csv(Answer, Options).
+csv(destroy(_Id, Wrapped), Options) :- !,
+	csv(Wrapped, Options).
+csv(success(_Id, Answers, Projection, _Time, More), Options) :- !,
+	VarTerm =.. [row|Projection],
 	success(Answers, VarTerm, [more(More)|Options]).
-csv(error(_Id, Error), _VarNames, _Options) :- !,
+csv(error(_Id, Error), _Options) :- !,
 	message_to_string(Error, Msg),
 	format('Status: 400 Bad request~n'),
 	format('Content-type: text/plain~n~n'),
 	format('ERROR: ~w~n', [Msg]).
-csv(output(_Id, message(_Term, _Class, HTML, _Where)), _VarNames, _Opts) :- !,
+csv(output(_Id, message(_Term, _Class, HTML, _Where)), _Opts) :- !,
 	format('Status: 400 Bad request~n'),
 	format('Content-type: text/html~n~n'),
 	format('<html>~n~s~n</html>~n', [HTML]).
-csv(page(Page, Event), VarNames, Options) :-
-	csv(Event, VarNames, [page(Page)|Options]).
-csv(failure(_Id, _Time), VarNames, Options) :- !,
-	VarTerm =.. [row|VarNames],
-	success([], VarTerm, [more(false)|Options]).
-csv(Event, _VarNames, _) :-
+csv(page(Page, Event), Options) :-
+	csv(Event, [page(Page)|Options]).
+csv(failure(_Id, _Time), Options) :- !,
+	success([], -, [more(false)|Options]).
+csv(Event, _) :-
 	print_term(Event, [output(user_error)]).
 
 success(Answers, VarTerm, Options) :-
@@ -112,10 +108,14 @@ success(Answers, VarTerm, Options) :-
 	format('Content-encoding: chunked~n'),
 	format('Content-disposition: attachment; filename="~w"~n', [Disposition]),
 	format('Content-type: text/csv~n~n'),
-	csv_write_stream(current_output, [VarTerm], []),
+	projection_row(VarTerm),
 	forall(paginate(100, Page, Rows),
 	       csv_write_stream(current_output, Page, [])).
 
+projection_row(-) :- !.
+projection_row(VarTerm) :-
+	csv_write_stream(current_output, [VarTerm], []).
+
 paginate(Len, Page, List) :-
 	length(Page0, Len),
 	(   append(Page0, Rest, List)
diff --git a/lib/swish/swish_debug.pl b/lib/swish/swish_debug.pl
index 89e2082..b589ff7 100644
--- a/lib/swish/swish_debug.pl
+++ b/lib/swish/swish_debug.pl
@@ -3,7 +3,7 @@
     Author:        Jan Wielemaker
     E-mail:        J.Wielemaker@vu.nl
     WWW:           http://www.swi-prolog.org
-    Copyright (c)  2015-2016, VU University Amsterdam
+    Copyright (c)  2015-2017, VU University Amsterdam
     All rights reserved.
 
     Redistribution and use in source and binary forms, with or without
@@ -33,11 +33,12 @@
 */
 
 :- module(swish_debug,
-	  [ pengine_stale_module/1,	% -Module, -State
+	  [ pengine_stale_module/1,	% -Module
 	    pengine_stale_module/2,	% -Module, -State
 	    swish_statistics/1,		% -Statistics
 	    start_swish_stat_collector/0,
-	    swish_stats/2		% ?Period, ?Dicts
+	    swish_stats/2,		% ?Period, ?Dicts
+	    swish_died_thread/2		% ?Thread, ?State
 	  ]).
 :- use_module(library(pengines)).
 :- use_module(library(broadcast)).
@@ -274,6 +275,7 @@ get_stats(Wrap, Stats) :-
 			rss:RSS,
 			stack:Stack,
 			pengines:Pengines,
+			threads:Threads,
 			pengines_created:PenginesCreated,
 			time:Time
 		      },
@@ -283,12 +285,14 @@ get_stats(Wrap, Stats) :-
 	statistics(cputime, MyCPU),
 	CPU is PCPU-MyCPU,
 	statistics(stack, Stack),
+	statistics(threads, Threads),
 	catch(procps_stat(Stat), _,
 	      Stat = stat{rss:0}),
 	RSS = Stat.rss,
 	swish_statistics(pengines(Pengines)),
 	swish_statistics(pengines_created(PenginesCreated)),
-	add_fordblks(Wrap, Stats0, Stats).
+	add_fordblks(Wrap, Stats0, Stats1),
+	add_visitors(Stats1, Stats).
 
 :- if(current_predicate(mallinfo/1)).
 add_fordblks(Wrap, Stats0, Stats) :-
@@ -303,6 +307,11 @@ add_fordblks(Wrap, Stats0, Stats) :-
 :- endif.
 add_fordblks(_, Stats, Stats).
 
+add_visitors(Stats0, Stats) :-
+	broadcast_request(swish(visitor_count(C))), !,
+	Stats = Stats0.put(visitors, C).
+add_visitors(Stats, Stats).
+
 
 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
 Maintain sliding statistics. The statistics are maintained in a ring. If
@@ -377,6 +386,24 @@ avg_key(Dicts, Len, Key, Key-Avg) :-
 	Avg is Sum/Len.
 
 
+%!	swish_died_thread(TID, Status) is nondet.
+%
+%	True if Id is a thread that died   with Status and has not (yet)
+%	been joined. Note that such threads may exist for a short while.
+
+swish_died_thread(TID, Status) :-
+	findall(TID-Stat, (thread_property(Thread, status(Stat)),
+			   Stat \== running,
+			   thread_property(Thread, id(TID))), Pairs),
+	member(TID-Stat, Pairs),
+	status_message(Stat, Status).
+
+status_message(exception(Ex), Message) :- !,
+	message_to_string(Ex, Message0),
+	string_concat('ERROR: ', Message0, Message).
+status_message(Status, Status).
+
+
 		 /*******************************
 		 *	     SANDBOX		*
 		 *******************************/
@@ -388,3 +415,4 @@ sandbox:safe_primitive(swish_debug:pengine_stale_module(_)).
 sandbox:safe_primitive(swish_debug:pengine_stale_module(_,_)).
 sandbox:safe_primitive(swish_debug:swish_statistics(_)).
 sandbox:safe_primitive(swish_debug:swish_stats(_, _)).
+sandbox:safe_primitive(swish_debug:swish_died_thread(_, _)).
diff --git a/web/bower_components/codemirror/mode/css/css.js b/web/bower_components/codemirror/mode/css/css.js
index 985287f..7f8c46e 100644
--- a/web/bower_components/codemirror/mode/css/css.js
+++ b/web/bower_components/codemirror/mode/css/css.js
@@ -28,6 +28,7 @@ CodeMirror.defineMode("css", function(config, parserConfig) {
       colorKeywords = parserConfig.colorKeywords || {},
       valueKeywords = parserConfig.valueKeywords || {},
       allowNested = parserConfig.allowNested,
+      lineComment = parserConfig.lineComment,
       supportsAtComponent = parserConfig.supportsAtComponent === true;
 
   var type, override;
@@ -253,6 +254,8 @@ CodeMirror.defineMode("css", function(config, parserConfig) {
   };
 
   states.pseudo = function(type, stream, state) {
+    if (type == "meta") return "pseudo";
+
     if (type == "word") {
       override = "variable-3";
       return state.context.type;
@@ -407,6 +410,7 @@ CodeMirror.defineMode("css", function(config, parserConfig) {
     electricChars: "}",
     blockCommentStart: "/*",
     blockCommentEnd: "*/",
+    lineComment: lineComment,
     fold: "brace"
   };
 });
@@ -524,7 +528,7 @@ CodeMirror.defineMode("css", function(config, parserConfig) {
     "transition-property", "transition-timing-function", "unicode-bidi",
     "user-select", "vertical-align", "visibility", "voice-balance", "voice-duration",
     "voice-family", "voice-pitch", "voice-range", "voice-rate", "voice-stress",
-    "voice-volume", "volume", "white-space", "widows", "width", "word-break",
+    "voice-volume", "volume", "white-space", "widows", "width", "will-change", "word-break",
     "word-spacing", "word-wrap", "z-index",
     // SVG-specific
     "clip-path", "clip-rule", "mask", "enable-background", "filter", "flood-color",
@@ -589,7 +593,7 @@ CodeMirror.defineMode("css", function(config, parserConfig) {
     "above", "absolute", "activeborder", "additive", "activecaption", "afar",
     "after-white-space", "ahead", "alias", "all", "all-scroll", "alphabetic", "alternate",
     "always", "amharic", "amharic-abegede", "antialiased", "appworkspace",
-    "arabic-indic", "armenian", "asterisks", "attr", "auto", "avoid", "avoid-column", "avoid-page",
+    "arabic-indic", "armenian", "asterisks", "attr", "auto", "auto-flow", "avoid", "avoid-column", "avoid-page",
     "avoid-region", "background", "backwards", "baseline", "below", "bidi-override", "binary",
     "bengali", "blink", "block", "block-axis", "bold", "bolder", "border", "border-box",
     "both", "bottom", "break", "break-all", "break-word", "bullets", "button", "button-bevel",
@@ -598,7 +602,7 @@ CodeMirror.defineMode("css", function(config, parserConfig) {
     "cell", "center", "checkbox", "circle", "cjk-decimal", "cjk-earthly-branch",
     "cjk-heavenly-stem", "cjk-ideographic", "clear", "clip", "close-quote",
     "col-resize", "collapse", "color", "color-burn", "color-dodge", "column", "column-reverse",
-    "compact", "condensed", "contain", "content",
+    "compact", "condensed", "contain", "content", "contents",
     "content-box", "context-menu", "continuous", "copy", "counter", "counters", "cover", "crop",
     "cross", "crosshair", "currentcolor", "cursive", "cyclic", "darken", "dashed", "decimal",
     "decimal-leading-zero", "default", "default-button", "dense", "destination-atop",
@@ -641,7 +645,7 @@ CodeMirror.defineMode("css", function(config, parserConfig) {
     "mix", "mongolian", "monospace", "move", "multiple", "multiply", "myanmar", "n-resize",
     "narrower", "ne-resize", "nesw-resize", "no-close-quote", "no-drop",
     "no-open-quote", "no-repeat", "none", "normal", "not-allowed", "nowrap",
-    "ns-resize", "numbers", "numeric", "nw-resize", "nwse-resize", "oblique", "octal", "open-quote",
+    "ns-resize", "numbers", "numeric", "nw-resize", "nwse-resize", "oblique", "octal", "opacity", "open-quote",
     "optimizeLegibility", "optimizeSpeed", "oriya", "oromo", "outset",
     "outside", "outside-shape", "overlay", "overline", "padding", "padding-box",
     "painted", "page", "paused", "persian", "perspective", "plus-darker", "plus-lighter",
@@ -653,7 +657,7 @@ CodeMirror.defineMode("css", function(config, parserConfig) {
     "rgb", "rgba", "ridge", "right", "rotate", "rotate3d", "rotateX", "rotateY",
     "rotateZ", "round", "row", "row-resize", "row-reverse", "rtl", "run-in", "running",
     "s-resize", "sans-serif", "saturation", "scale", "scale3d", "scaleX", "scaleY", "scaleZ", "screen",
-    "scroll", "scrollbar", "se-resize", "searchfield",
+    "scroll", "scrollbar", "scroll-position", "se-resize", "searchfield",
     "searchfield-cancel-button", "searchfield-decoration",
     "searchfield-results-button", "searchfield-results-decoration",
     "semi-condensed", "semi-expanded", "separate", "serif", "show", "sidama",
@@ -663,7 +667,7 @@ CodeMirror.defineMode("css", function(config, parserConfig) {
     "small", "small-caps", "small-caption", "smaller", "soft-light", "solid", "somali",
     "source-atop", "source-in", "source-out", "source-over", "space", "space-around", "space-between", "spell-out", "square",
     "square-button", "start", "static", "status-bar", "stretch", "stroke", "sub",
-    "subpixel-antialiased", "super", "sw-resize", "symbolic", "symbols", "table",
+    "subpixel-antialiased", "super", "sw-resize", "symbolic", "symbols", "system-ui", "table",
     "table-caption", "table-cell", "table-column", "table-column-group",
     "table-footer-group", "table-header-group", "table-row", "table-row-group",
     "tamil",
@@ -671,9 +675,9 @@ CodeMirror.defineMode("css", function(config, parserConfig) {
     "thick", "thin", "threeddarkshadow", "threedface", "threedhighlight",
     "threedlightshadow", "threedshadow", "tibetan", "tigre", "tigrinya-er",
     "tigrinya-er-abegede", "tigrinya-et", "tigrinya-et-abegede", "to", "top",
-    "trad-chinese-formal", "trad-chinese-informal",
+    "trad-chinese-formal", "trad-chinese-informal", "transform",
     "translate", "translate3d", "translateX", "translateY", "translateZ",
-    "transparent", "ultra-condensed", "ultra-expanded", "underline", "up",
+    "transparent", "ultra-condensed", "ultra-expanded", "underline", "unset", "up",
     "upper-alpha", "upper-armenian", "upper-greek", "upper-hexadecimal",
     "upper-latin", "upper-norwegian", "upper-roman", "uppercase", "urdu", "url",
     "var", "vertical", "vertical-text", "visible", "visibleFill", "visiblePainted",
@@ -730,6 +734,7 @@ CodeMirror.defineMode("css", function(config, parserConfig) {
     valueKeywords: valueKeywords,
     fontProperties: fontProperties,
     allowNested: true,
+    lineComment: "//",
     tokenHooks: {
       "/": function(stream, state) {
         if (stream.eat("/")) {
@@ -743,8 +748,8 @@ CodeMirror.defineMode("css", function(config, parserConfig) {
         }
       },
       ":": function(stream) {
-        if (stream.match(/\s*\{/))
-          return [null, "{"];
+        if (stream.match(/\s*\{/, false))
+          return [null, null]
         return false;
       },
       "$": function(stream) {
@@ -772,6 +777,7 @@ CodeMirror.defineMode("css", function(config, parserConfig) {
     valueKeywords: valueKeywords,
     fontProperties: fontProperties,
     allowNested: true,
+    lineComment: "//",
     tokenHooks: {
       "/": function(stream, state) {
         if (stream.eat("/")) {
diff --git a/web/bower_components/codemirror/mode/htmlmixed/htmlmixed.js b/web/bower_components/codemirror/mode/htmlmixed/htmlmixed.js
index eb21fcc..16b4f13 100644
--- a/web/bower_components/codemirror/mode/htmlmixed/htmlmixed.js
+++ b/web/bower_components/codemirror/mode/htmlmixed/htmlmixed.js
@@ -14,7 +14,7 @@
   var defaultTags = {
     script: [
       ["lang", /(javascript|babel)/i, "javascript"],
-      ["type", /^(?:text|application)\/(?:x-)?(?:java|ecma)script$|^$/i, "javascript"],
+      ["type", /^(?:text|application)\/(?:x-)?(?:java|ecma)script$|^module$|^$/i, "javascript"],
       ["type", /./, "text/plain"],
       [null, null, "javascript"]
     ],
diff --git a/web/bower_components/codemirror/mode/javascript/javascript.js b/web/bower_components/codemirror/mode/javascript/javascript.js
index a717745..7c09476 100644
--- a/web/bower_components/codemirror/mode/javascript/javascript.js
+++ b/web/bower_components/codemirror/mode/javascript/javascript.js
@@ -12,7 +12,7 @@
 "use strict";
 
 function expressionAllowed(stream, state, backUp) {
-  return /^(?:operator|sof|keyword c|case|new|[\[{}\(,;:]|=>)$/.test(state.lastType) ||
+  return /^(?:operator|sof|keyword c|case|new|export|default|[\[{}\(,;:]|=>)$/.test(state.lastType) ||
     (state.lastType == "quasi" && /\{\s*$/.test(stream.string.slice(0, stream.pos - (backUp || 0))))
 }
 
@@ -77,7 +77,7 @@ CodeMirror.defineMode("javascript", function(config, parserConfig) {
     return jsKeywords;
   }();
 
-  var isOperatorChar = /[+\-*&%=<>!?|~^]/;
+  var isOperatorChar = /[+\-*&%=<>!?|~^@]/;
   var isJsonldKeyword = /^@(context|id|value|language|type|container|list|set|reverse|index|base|vocab|graph)"/;
 
   function readRegexp(stream) {
@@ -146,7 +146,8 @@ CodeMirror.defineMode("javascript", function(config, parserConfig) {
       stream.skipToEnd();
       return ret("error", "error");
     } else if (isOperatorChar.test(ch)) {
-      stream.eatWhile(isOperatorChar);
+      if (ch != ">" || !state.lexical || state.lexical.type != ">")
+        stream.eatWhile(isOperatorChar);
       return ret("operator", "operator", stream.current());
     } else if (wordRE.test(ch)) {
       stream.eatWhile(wordRE);
@@ -373,6 +374,7 @@ CodeMirror.defineMode("javascript", function(config, parserConfig) {
     if (type == "module") return cont(pushlex("form"), pattern, pushlex("}"), expect("{"), block, poplex, poplex)
     if (type == "type") return cont(typeexpr, expect("operator"), typeexpr, expect(";"));
     if (type == "async") return cont(statement)
+    if (value == "@") return cont(expression, statement)
     return pass(pushlex("stat"), expression, expect(";"), poplex);
   }
   function expression(type) {
@@ -504,9 +506,9 @@ CodeMirror.defineMode("javascript", function(config, parserConfig) {
     if (type == ":") return cont(expressionNoComma);
     if (type == "(") return pass(functiondef);
   }
-  function commasep(what, end) {
+  function commasep(what, end, sep) {
     function proceed(type, value) {
-      if (type == ",") {
+      if (sep ? sep.indexOf(type) > -1 : type == ",") {
         var lex = cx.state.lexical;
         if (lex.info == "call") lex.pos = (lex.pos || 0) + 1;
         return cont(function(type, value) {
@@ -539,16 +541,19 @@ CodeMirror.defineMode("javascript", function(config, parserConfig) {
   }
   function typeexpr(type) {
     if (type == "variable") {cx.marked = "variable-3"; return cont(afterType);}
-    if (type == "{") return cont(commasep(typeprop, "}"))
+    if (type == "string" || type == "number" || type == "atom") return cont(afterType);
+    if (type == "{") return cont(pushlex("}"), commasep(typeprop, "}", ",;"), poplex)
     if (type == "(") return cont(commasep(typearg, ")"), maybeReturnType)
   }
   function maybeReturnType(type) {
     if (type == "=>") return cont(typeexpr)
   }
-  function typeprop(type) {
+  function typeprop(type, value) {
     if (type == "variable" || cx.style == "keyword") {
       cx.marked = "property"
       return cont(typeprop)
+    } else if (value == "?") {
+      return cont(typeprop)
     } else if (type == ":") {
       return cont(typeexpr)
     }
@@ -558,7 +563,8 @@ CodeMirror.defineMode("javascript", function(config, parserConfig) {
     else if (type == ":") return cont(typeexpr)
   }
   function afterType(type, value) {
-    if (value == "<") return cont(commasep(typeexpr, ">"), afterType)
+    if (value == "<") return cont(pushlex(">"), commasep(typeexpr, ">"), poplex, afterType)
+    if (value == "|" || type == ".") return cont(typeexpr)
     if (type == "[") return cont(expect("]"), afterType)
   }
   function vardef() {
@@ -615,6 +621,7 @@ CodeMirror.defineMode("javascript", function(config, parserConfig) {
     if (value == "*") {cx.marked = "keyword"; return cont(functiondef);}
     if (type == "variable") {register(value); return cont(functiondef);}
     if (type == "(") return cont(pushcontext, pushlex(")"), commasep(funarg, ")"), poplex, maybetype, statement, popcontext);
+    if (isTS && value == "<") return cont(pushlex(">"), commasep(typeexpr, ">"), poplex, functiondef)
   }
   function funarg(type) {
     if (type == "spread") return cont(funarg);
@@ -629,12 +636,14 @@ CodeMirror.defineMode("javascript", function(config, parserConfig) {
     if (type == "variable") {register(value); return cont(classNameAfter);}
   }
   function classNameAfter(type, value) {
-    if (value == "extends" || value == "implements") return cont(isTS ? typeexpr : expression, classNameAfter);
+    if (value == "<") return cont(pushlex(">"), commasep(typeexpr, ">"), poplex, classNameAfter)
+    if (value == "extends" || value == "implements" || (isTS && type == ","))
+      return cont(isTS ? typeexpr : expression, classNameAfter);
     if (type == "{") return cont(pushlex("}"), classBody, poplex);
   }
   function classBody(type, value) {
     if (type == "variable" || cx.style == "keyword") {
-      if ((value == "static" || value == "get" || value == "set" ||
+      if ((value == "async" || value == "static" || value == "get" || value == "set" ||
            (isTS && (value == "public" || value == "private" || value == "protected" || value == "readonly" || value == "abstract"))) &&
           cx.stream.match(/^\s+[\w$\xa1-\uffff]/, false)) {
         cx.marked = "keyword";
@@ -643,26 +652,35 @@ CodeMirror.defineMode("javascript", function(config, parserConfig) {
       cx.marked = "property";
       return cont(isTS ? classfield : functiondef, classBody);
     }
+    if (type == "[")
+      return cont(expression, expect("]"), isTS ? classfield : functiondef, classBody)
     if (value == "*") {
       cx.marked = "keyword";
       return cont(classBody);
     }
     if (type == ";") return cont(classBody);
     if (type == "}") return cont();
+    if (value == "@") return cont(expression, classBody)
   }
   function classfield(type, value) {
     if (value == "?") return cont(classfield)
     if (type == ":") return cont(typeexpr, maybeAssign)
+    if (value == "=") return cont(expressionNoComma)
     return pass(functiondef)
   }
-  function afterExport(_type, value) {
+  function afterExport(type, value) {
     if (value == "*") { cx.marked = "keyword"; return cont(maybeFrom, expect(";")); }
     if (value == "default") { cx.marked = "keyword"; return cont(expression, expect(";")); }
+    if (type == "{") return cont(commasep(exportField, "}"), maybeFrom, expect(";"));
     return pass(statement);
   }
+  function exportField(type, value) {
+    if (value == "as") { cx.marked = "keyword"; return cont(expect("variable")); }
+    if (type == "variable") return pass(expressionNoComma, exportField);
+  }
   function afterImport(type) {
     if (type == "string") return cont();
-    return pass(importSpec, maybeFrom);
+    return pass(importSpec, maybeMoreImports, maybeFrom);
   }
   function importSpec(type, value) {
     if (type == "{") return contCommasep(importSpec, "}");
@@ -670,6 +688,9 @@ CodeMirror.defineMode("javascript", function(config, parserConfig) {
     if (value == "*") cx.marked = "keyword";
     return cont(maybeAs);
   }
+  function maybeMoreImports(type) {
+    if (type == ",") return cont(importSpec, maybeMoreImports)
+  }
   function maybeAs(_type, value) {
     if (value == "as") { cx.marked = "keyword"; return cont(importSpec); }
   }
diff --git a/web/css/swish-min.css b/web/css/swish-min.css
index aa9d87e..950088e 100644
--- a/web/css/swish-min.css
+++ b/web/css/swish-min.css
@@ -1,14 +1,10 @@
-ul.dropdown-menu li.checkbox input{margin-left:3px}ul.dropdown-menu li.checkbox span{margin-left:20px}.dropdown-menu>li{position:relative;-webkit-user-select:none;-moz-user-select:none;-ms-user-select:none;-o-user-select:none;user-select:none;cursor:pointer}.dropdown-menu .sub-menu{left:100%;position:absolute;top:0;display:none;margin-top:-1px;border-top-left-radius:0;border-bottom-left-radius:0;border-left-color:#fff;box-shadow:none}.left-caret:after,.right-caret:after{content:"";border-bottom:5px solid transparent;border-top:5px solid transparent;display:inline-block;height:0;vertical-align:middle;width:0;margin-left:5px}.right-caret:after{border-left:5px solid #ffaf46}.left-caret:after{border-right:5px solid #ffaf46}.dropdown-icon{margin-left:-12px;margin-right:5px;padding:0;background-repeat:no-repeat;background-size:100%;background-position:50% 50%;display:inline-block;vertical-align:middle;height:18px;width:18px}a.accelerated{position:relative}a.accelerated span.accell-spacer{color:#fff}a.accelerated span.accell-text{color:#888;position:absolute;right:10px}body,html{width:100%;height:100%;padding:0;margin:0;overflow:hidden}nav.navbar{margin-bottom:5px}#content{width:100%;height:calc(100% - 55px);padding:0;background-color:#fff}.pane-container,.pane-wrapper{width:100%;height:100%;background-color:white:green}.splittable{background-color:#fff;width:100%;height:100%;padding:5px}div.tabbed{height:100%}div.tab-content{height:calc(100% - 40px)}div.tab-pane{position:relative;height:100%}span.glyphicon.xclose:hover{opacity:.8}span.glyphicon.xclose{margin-left:5px;opacity:.2}a.tab-new.compact>span{padding:6px 0}.nav>li>a.compact{padding:0 5px}span.tab-dirty{display:none;background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAADAAAAAqCAMAAADCkShIAAAAIGNIUk0AAHomAACAhAAA+gAAAIDoAAB1MAAA6mAAADqYAAAXcJy6UTwAAAAzUExURQAAAAICAQAAAAAAADAwHSkoFVtYJvj4wdHPi/37sKOfVvv3joJ+OfLsa6GaOfryVf////09bBAAAAAGdFJOUwD+LWbH9lfFP3wAAAABYktHRBCVsg0sAAAACXBIWXMAAAsTAAALEwEAmpwYAAAAB3RJTUUH4AkVDAQs7+kkfQAAAetJREFUSMeVVY3WqjAMc7B1XffT93/bm3aA+l1Q7FGBQ7I0WcHH47RCCMvjhwpe9/Fr+JEBLMV4nwCBmHO8LwFkzplvEyBAIGS62dSClUveJNZ7DUn2kltNBXdsVcqNaBdriA1tX77hYndcTIG/RwuByAysFzO277sA84RXENoXidUFeMJLrcX2e/kcETthwvH5HG3YHZfWGHCrj763SNm3jCehfyBMAWYxq8HQRFLpmuFT6tnbdltLduyXj+scoolv1NFN9dNxIWE3s9BcfvbvBOrpfGrdcdgILEAJoGlIP4/WHVPYHOAChgGl3lXPJOxFwaUdhAQL3WRSU9UT3+YuF9k82FWv1rydqf4/UqvnWHh6ADAKUdrEziQsUpsdw8fQrHU53IDwN9p9o2qVKEgT+N7piVelN9/Lc3SqIMxkBJVXwnhrCl2QC/TOJAYUnRkdhDeJNURrxIcNVmGW6K/Cm2937AJkX3RPXZ2QXgjPaPfZsXHbC3gdYwI3wnO/Xxx3o+hF7dGaKrJJNGyzMNcNvworNKiNNCg1nI20+14QEaNzkljTAEwHnKvBSVvCVRoDhDa2aGGg1WppjiRYU3BXAVWDYWFo2sEU1J9Wm67KdRrWawdHUNvsH5VOT2f523z/x7xZ6+M3xvr4B2dMHj70RasaAAAAAElFTkSuQmCC);padding:0;background-repeat:no-repeat;background-size:90% 60%;background-position:0 40%;vertical-align:middle;height:30px;width:21px}.nav>li>a.compact.data-dirty>span.tab-dirty{display:inline-block}.tabbed-select:{width:100%}.tabbed-create{margin:2em 0 1em;text-align:center}label.tabbed-left{text-align:right;margin-right:.6em;white-space:nowrap;width:5em}label.tabbed-right{text-align:left;margin-left:.6em;white-space:nowrap;width:5em}.tabbed-profile>label{font-style:italic;font-weight:400;color:#888}.tab-icon{padding:0;background-repeat:no-repeat;background-size:70%;background-position:50% 40%;display:inline-block;vertical-align:middle;height:30px;width:30px}.tabbed-profile{width:100%;text-align:center}.tabbed-profile .select-profile{display:inline-block}form.search-sources{margin:3em auto 1em;width:80%}.CodeMirror{font-family:monospace;color:#000}.CodeMirror-lines{padding:4px 0}.CodeMirror pre{padding:0 4px}.CodeMirror-gutter-filler,.CodeMirror-scrollbar-filler{background-color:#fff}.CodeMirror-gutters{border-right:1px solid #ddd;background-color:#f7f7f7;white-space:nowrap}.CodeMirror-linenumber{padding:0 3px 0 5px;min-width:20px;text-align:right;color:#999;white-space:nowrap}.CodeMirror-guttermarker{color:#000}.CodeMirror-guttermarker-subtle{color:#999}.CodeMirror-cursor{border-left:1px solid #000;border-right:none;width:0}.CodeMirror div.CodeMirror-secondarycursor{border-left:1px solid silver}.cm-fat-cursor .CodeMirror-cursor{width:auto;border:0!important;background:#7e7}.cm-fat-cursor div.CodeMirror-cursors{z-index:1}.cm-animate-fat-cursor{width:auto;border:0;-webkit-animation:blink 1.06s steps(1) infinite;-moz-animation:blink 1.06s steps(1) infinite;animation:blink 1.06s steps(1) infinite;background-color:#7e7}@-moz-keyframes blink{50%{background-color:transparent}}@-webkit-keyframes blink{50%{background-color:transparent}}@keyframes blink{50%{background-color:transparent}}.cm-tab{display:inline-block;text-decoration:inherit}.CodeMirror-rulers{position:absolute;left:0;right:0;top:-50px;bottom:-20px;overflow:hidden}.CodeMirror-ruler{border-left:1px solid #ccc;top:0;bottom:0;position:absolute}.cm-s-default .cm-header{color:#00f}.cm-s-default .cm-quote{color:#090}.cm-negative{color:#d44}.cm-positive{color:#292}.cm-header,.cm-strong{font-weight:700}.cm-em{font-style:italic}.cm-link{text-decoration:underline}.cm-strikethrough{text-decoration:line-through}.cm-s-default .cm-keyword{color:#708}.cm-s-default .cm-atom{color:#219}.cm-s-default .cm-number{color:#164}.cm-s-default .cm-def{color:#00f}.cm-s-default .cm-variable-2{color:#05a}.cm-s-default .cm-variable-3{color:#085}.cm-s-default .cm-comment{color:#a50}.cm-s-default .cm-string{color:#a11}.cm-s-default .cm-string-2{color:#f50}.cm-s-default .cm-meta,.cm-s-default .cm-qualifier{color:#555}.cm-s-default .cm-builtin{color:#30a}.cm-s-default .cm-bracket{color:#997}.cm-s-default .cm-tag{color:#170}.cm-s-default .cm-attribute{color:#00c}.cm-s-default .cm-hr{color:#999}.cm-s-default .cm-link{color:#00c}.cm-invalidchar,.cm-s-default .cm-error{color:red}.CodeMirror-composing{border-bottom:2px solid}div.CodeMirror span.CodeMirror-matchingbracket{color:#0f0}div.CodeMirror span.CodeMirror-nonmatchingbracket{color:#f22}.CodeMirror-matchingtag{background:rgba(255,150,0,.3)}.CodeMirror-activeline-background{background:#e8f2ff}.CodeMirror{position:relative;overflow:hidden;background:#fff}.CodeMirror-scroll{overflow:scroll!important;margin-bottom:-30px;margin-right:-30px;padding-bottom:30px;height:100%;outline:0;position:relative}.CodeMirror-sizer{position:relative;border-right:30px solid transparent}.CodeMirror-gutter-filler,.CodeMirror-hscrollbar,.CodeMirror-scrollbar-filler,.CodeMirror-vscrollbar{position:absolute;z-index:6;display:none}.CodeMirror-vscrollbar{right:0;top:0;overflow-x:hidden;overflow-y:scroll}.CodeMirror-hscrollbar{bottom:0;left:0;overflow-y:hidden;overflow-x:scroll}.CodeMirror-scrollbar-filler{right:0;bottom:0}.CodeMirror-gutter-filler{left:0;bottom:0}.CodeMirror-gutters{position:absolute;left:0;top:0;min-height:100%;z-index:3}.CodeMirror-gutter{white-space:normal;height:100%;display:inline-block;vertical-align:top;margin-bottom:-30px}.CodeMirror-gutter-wrapper{position:absolute;z-index:4;background:none!important;border:none!important}.CodeMirror-gutter-background{position:absolute;top:0;bottom:0;z-index:4}.CodeMirror-gutter-elt{position:absolute;cursor:default;z-index:4}.CodeMirror-gutter-wrapper{-webkit-user-select:none;-moz-user-select:none;user-select:none}.CodeMirror-lines{cursor:text;min-height:1px}.CodeMirror pre{-moz-border-radius:0;-webkit-border-radius:0;border-radius:0;border-width:0;background:0 0;font-family:inherit;font-size:inherit;margin:0;white-space:pre;word-wrap:normal;line-height:inherit;color:inherit;z-index:2;position:relative;overflow:visible;-webkit-tap-highlight-color:transparent;-webkit-font-variant-ligatures:none;font-variant-ligatures:none}.CodeMirror-wrap pre{word-wrap:break-word;white-space:pre-wrap;word-break:normal}.CodeMirror-linebackground{position:absolute;left:0;right:0;top:0;bottom:0;z-index:0}.CodeMirror-linewidget{position:relative;z-index:2;overflow:auto}.CodeMirror-code{outline:0}.CodeMirror-gutter,.CodeMirror-gutters,.CodeMirror-linenumber,.CodeMirror-scroll,.CodeMirror-sizer{-moz-box-sizing:content-box;box-sizing:content-box}.CodeMirror-measure{position:absolute;width:100%;height:0;overflow:hidden;visibility:hidden}.CodeMirror-cursor{position:absolute;pointer-events:none}.CodeMirror-measure pre{position:static}div.CodeMirror-cursors{visibility:hidden;position:relative;z-index:3}.CodeMirror-focused div.CodeMirror-cursors,div.CodeMirror-dragcursors{visibility:visible}.CodeMirror-selected{background:#d9d9d9}.CodeMirror-focused .CodeMirror-selected{background:#d7d4f0}.CodeMirror-crosshair{cursor:crosshair}.CodeMirror-line::selection,.CodeMirror-line>span::selection,.CodeMirror-line>span>span::selection{background:#d7d4f0}.CodeMirror-line::-moz-selection,.CodeMirror-line>span::-moz-selection,.CodeMirror-line>span>span::-moz-selection{background:#d7d4f0}.cm-searching{background:#ffa;background:rgba(255,255,0,.4)}.cm-force-border{padding-right:.1px}@media print{.CodeMirror div.CodeMirror-cursors{visibility:hidden}}.cm-tab-wrap-hack:after{content:''}span.CodeMirror-selectedtext{background:0 0}.CodeMirror-hints{position:absolute;z-index:10;overflow:hidden;list-style:none;margin:0;padding:2px;-webkit-box-shadow:2px 3px 5px rgba(0,0,0,.2);-moz-box-shadow:2px 3px 5px rgba(0,0,0,.2);box-shadow:2px 3px 5px rgba(0,0,0,.2);border-radius:3px;border:1px solid silver;background:#fff;font-size:90%;font-family:monospace;max-height:20em;overflow-y:auto}.CodeMirror-hint{margin:0;padding:0 4px;border-radius:2px;white-space:pre;color:#000;cursor:pointer}li.CodeMirror-hint-active{background:#08f;color:#fff}.CodeMirror-dialog{position:absolute;left:0;right:0;background:inherit;z-index:15;padding:.1em .8em;overflow:hidden;color:inherit}.CodeMirror-dialog-top{border-bottom:1px solid #eee;top:0}.CodeMirror-dialog-bottom{border-top:1px solid #eee;bottom:0}.CodeMirror-dialog input{border:none;outline:0;background:0 0;width:20em;color:inherit;font-family:monospace}.CodeMirror-dialog button{font-size:70%}.cm-s-prolog span.cm-neg-number,.cm-s-prolog span.cm-number{color:#000}.cm-s-prolog span.cm-atom,.cm-s-prolog span.cm-uatom{color:#762}.cm-s-prolog span.cm-qatom{color:#008}.cm-s-prolog span.cm-string,.cm-s-prolog span.cm-string_terminal{color:#008;font-style:italic}.cm-s-prolog span.cm-bqstring,.cm-s-prolog span.cm-chars,.cm-s-prolog span.cm-codes{color:#040;font-style:italic}.cm-s-prolog span.cm-functor{color:#000;font-style:italic}.cm-s-prolog span.cm-ext_quant,.cm-s-prolog span.cm-key,.cm-s-prolog span.cm-tag{color:#000;font-weight:700}.cm-s-prolog span.cm-qq_content{color:#900}.cm-s-prolog span.cm-qq_close,.cm-s-prolog span.cm-qq_open,.cm-s-prolog span.cm-qq_sep{color:#00f;font-weight:700}.cm-s-prolog span.cm-qq_type{font-weight:700}.cm-s-prolog span.cm-comment,.cm-s-prolog span.cm-comment_string{color:#060;font-style:italic;line-height:1em}.cm-s-prolog span.cm-var{color:#800}.cm-s-prolog span.cm-var-2{color:#888}.cm-s-prolog span.cm-anon{color:#800}.cm-s-prolog span.cm-singleton{color:#800;font-weight:700}.cm-s-prolog span.cm-identifier{font-weight:700}.cm-s-prolog span.cm-module{color:#549}.cm-s-prolog span.cm-head_exported{color:#00f;font-weight:700}.cm-s-prolog span.cm-head_unreferenced{color:red;font-weight:700}.cm-s-prolog span.cm-head_built_in,.cm-s-prolog span.cm-head_iso{background:orange;font-weight:700}.cm-s-prolog span.cm-head_hook{color:#00f;text-decoration:underline}.cm-s-prolog span.cm-head_extern{color:#00f;font-weight:700}.cm-s-prolog span.cm-head_public{color:#016300;font-weight:700}.cm-s-prolog span.cm-head_constraint{color:#008b8b;font-weight:700}.cm-s-prolog span.cm-head{font-weight:700}.cm-s-prolog span.cm-goal_built_in,.cm-s-prolog span.cm-goal_imported{color:#00f}.cm-s-prolog span.cm-goal_autoload{color:#008}.cm-s-prolog span.cm-goal_undefined{color:red}.cm-s-prolog span.cm-goal_dynamic{color:#f0f}.cm-s-prolog span.cm-goal_thread_local{color:#f0f;text-decoration:underline}.cm-s-prolog span.cm-goal_constraint{color:#008b8b}.cm-s-prolog span.cm-goal_recursion{text-decoration:underline}.cm-s-prolog span.cm-meta,.cm-s-prolog span.cm-op_type{color:#00f}.cm-s-prolog span.cm-file_no_depends{color:#00f;text-decoration:underline;background:#fcd}.cm-s-prolog span.cm-file{color:#00f;text-decoration:underline}.cm-s-prolog span.cm-nofile{color:red}.cm-s-prolog span.cm-option_name{color:#3434ba}.cm-s-prolog span.cm-no_option_name{color:red}.cm-s-prolog span.cm-flag_name{color:#00f}.cm-s-prolog span.cm-no_flag_name{color:red}.cm-s-prolog span.cm-error,.cm-s-prolog span.cm-instantiation_error{border-bottom:2px dotted red}.cm-s-prolog span.cm-link{color:#762}.cm-s-prolog span.cm-expanded{color:#00f;text-decoration:underline}.cm-s-prolog span.cm-undefined_import{color:red}.cm-s-prolog span.cm-unused_import{color:#00f;background:pink}.cm-s-prolog span.cm-xpce_method{font-weight:700}.cm-s-prolog span.cm-xpce_class_built_in{color:#00f}.cm-s-prolog span.cm-xpce_class_lib{color:#00f;font-style:italic}.cm-s-prolog span.cm-xpce_class_undef,.cm-s-prolog span.cm-xpce_class_user{color:#000;font-style:italic}.cm-s-prolog span.cm-outofsync{border:1px dotted red}.cm-s-prolog span.cm-html{color:#909;font-weight:700}.cm-s-prolog span.cm-entity,.cm-s-prolog span.cm-html_attribute{color:#909}.cm-s-prolog span.cm-sgml_attr_function{color:#00f}.cm-s-prolog span.cm-http_location_for_id{font-weight:700}.cm-s-prolog span.cm-http_no_location_for_id{color:red;font-weight:700}.cm-jumped{background:#ff0}.CodeMirror-hover-tooltip{background-color:infobackground;border:1px solid #000;border-radius:4px;color:infotext;font-size:10pt;overflow:hidden;padding:2px 5px;position:fixed;z-index:100;max-width:600px;opacity:0;transition:opacity .4s;-moz-transition:opacity .4s;-webkit-transition:opacity .4s;-o-transition:opacity .4s;-ms-transition:opacity .4s}.CodeMirror-hover-tooltip .pred-name{color:#00f;font-family:monospace;margin-right:5px}.CodeMirror-hover-tooltip .pred-tag{font-weight:700;margin-right:5px}.CodeMirror-hover-tooltip .pred-summary{font-style:italic}.CodeMirror-templates-variable{outline:#4664A5 solid 1px}.CodeMirror-templates-variable-selected{background-color:#B4D7FF}.CodeMirror-hint-template{background:url(data:image/gif;base64,R0lGODlhEAAQANUAAH5weoJ1g4h8kY+EoZaMsZyTv6CYyGd9qWqArG+Fr3aLs3yRuIKXvYmdwY2hxIaUroiVrIyXqoidwZGlx4+aqJScpfr9//f8//b8//n9/9Xz/+v5/5ifovH7/+n5/+36//D7//T8/+r6/+v6//P8//f9//b9//r+//n+/56inqKlm6iol62rlP7xevzndvjQasiYQP///wAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAACH5BAEAADEALAAAAAAQABAAAAaEwJhwSCwOYcikEkmEtZ7QKKzpMhgKhIEgAHBNj6+wePwVsjTotJpFXGk88Hh8RVRpJo4GY6FIIDwqRCkaIxuFIoUjIylEHHd5e30IHxxEFRogIB2ZmpoVRBR3EgsJByGnJBREERolFyWwJhgmJRFEEBonFigoFhYZvRBED8TFxsRGyUVBADs=) left center no-repeat;padding-left:18px;margin:3px 0}.CodeMirror-hints-contextInfo{position:absolute;z-index:10;border:3px double #d4d0c8;max-height:200px;max-width:400px;min-width:400px;overflow:auto;background:#FFFFE1;font-family:Tahoma;font-size:12px;padding:5px}.CodeMirror-hints{overflow-x:visible}.CodeMirror-hint{position:relative;max-width:none;overflow:visible}.CodeMirror-hint-description{display:none}.CodeMirror-hint-description.active{display:block;position:absolute;z-index:20;left:10px;top:0}.CodeMirror,.prolog-editor{height:100%}.CodeMirror pre.CodeMirror-placeholder{color:#999}.CodeMirror .source-msg.error{color:red;border-left:2px solid red}.CodeMirror .source-msg{position:relative;border-left:2px solid #000;padding:0 5px;background-color:#ddd;cursor:hand;cursor:pointer}.CodeMirror .source-msg>span.glyphicon{color:#000;position:absolute;right:5px;top:5px}.CodeMirror .source-msg-charmark{height:1.5ex}.CodeMirror .source-msg:hover{text-decoration:line-through}.CodeMirror-hover{outline:grey solid 1px}.CodeMirror-search-match,.CodeMirror-target-line{background-color:#ff0}.CodeMirror-search-alt-match{background-color:#bee}.CodeMirror .trace.call,.CodeMirror .trace.exit{background-color:#0f0}.CodeMirror .trace.fail{background-color:red}.CodeMirror .trace.redo{background-color:#ff0}.CodeMirror .trace.exception{background-color:#f0f}.Prolog-breakpoints{width:1em}.breakpoint-marker{color:#822;padding-left:4px;font-size:120%;position:relative;top:-.2em}div.edit-modal{position:absolute;left:0;right:0;top:0;bottom:0;z-index:2000}div.edit-modal>div.mask{position:absolute;left:0;right:0;top:0;bottom:0;background:#000;opacity:.2}div.edit-modal .goto-source{position:absolute;padding:.2em .5em 0;border-radius:5px;border:1px solid #000;background:#fff;box-shadow:10px 10px 5px #888;z-index:2001}div.CodeMirror-dialog{border:1px solid #888;background:#f8f8f8;box-shadow:10px 10px 5px #888}div.prolog-query{height:100%;padding:5px;background-color:#eee;position:relative}.prolog-query-editor .buttons-left{display:block;position:absolute;bottom:10px}.prolog-query-editor .buttons-right{display:block;position:absolute;bottom:10px;right:5px}.prolog-query-editor div.prolog-prompt{position:absolute;top:5px;left:10px;heigth:100%;vertical-align:top;font-weight:700}.prolog-query-editor div.query{margin-top:3px;height:calc(100% - 35px);margin-left:2em}.prolog-query-editor div.query-buttons{margin-left:2em}span.run-chk-table{margin-right:5px;color:#777}span.run-chk-table input{position:relative;top:2px}ul.dropdown-menu.history{max-height:30ex;overflow:auto}div.prolog-runners{width:100%;height:100%;background-image:url(../icons/owl_25_years.png);background-size:90%;background-repeat:no-repeat;background-position:35% 50%;overflow:auto;padding:0 5px}div.prolog-runner{position:relative;margin:2px 0;border:1px solid #ccc;border-radius:5px}div.prolog-runner.tabled{border:0}div.prolog-runner>a.close{position:absolute;top:-4px;right:-10px;z-index:10}div.prolog-runner:focus{outline:0}div.prolog-runner.iconic>div.runner-results{display:none}div.runner-title{padding:0 5px 2px;border-width:2px;border-radius:5px;box-sizing:border-box}div.prolog-runner:focus div.runner-title{border:2px solid #000}div.runner-results{padding:2px 0;background-color:#fff;border-radius:5px}span.answer-no{float:right;color:#060;font-size:80%;margin-right:2px;font-style:italic}div.answer{padding-left:5px;border-radius:5px}div.answer.even{background-color:#eee}div.answer.odd{background-color:#fff}div.response{font-style:italic;color:#00f;font-size:90%;margin-left:10%;background-color:#eee;border:1px solid #ccc;border-radius:5px;padding:0 5px}span.prolog-true{font-weight:700}span.prolog-false{font-weight:700;color:red}div.cputime{text-align:right}div.cputime span{background-color:#ccc;border-radius:5px;border:1px solid #888;padding:0 5px;font-size:80%;font-style:italic;color:#060}span.runner-state{position:relative;top:2px;width:1.5em;height:1.5em;margin-right:5px;background-size:100%;background-repeat:no-repeat;display:inline-block}div.runners-menu{position:absolute;top:3px;right:5px;z-index:2000}div.runner-title button.dropdown-toggle{background:none;border:0;cursor:pointer;padding:0}div.runner-title>button{background:none;border:0;cursor:pointer;padding:3px 0;color:#000;float:right;font-size:21px;font-weight:700;line-height:1;opacity:.2;text-shadow:0 1px 0 #fff;margin-left:5px}div.runner-title>button.rtb-toggleIconic{padding:8px 0}div.runner-title>button:hover{opacity:.8}span.runner-state.idle,span.runner-state.wait-input,span.runner-state.wait-next{background-image:url(../icons/logo.png)}span.runner-state.wait-debug{background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAACAAAAAgCAYAAABzenr0AAAABmJLR0QA/wD/AP+gvaeTAAAACXBIWXMAAAsTAAALEwEAmpwYAAAAB3RJTUUH3wMfEyg27OEfWQAAAYdJREFUWMPtVsFtwzAMJINMwlHyt0foCIW6gUYQMkJGsP8dRauwH9GQacqiDffThoARR6LE4/EoGeBt/93w6AIG4J3N8FcA7AXVm/BBMDdP8JkIsASqHx20BtMD7bKJiBnAfErc5nzld31wDQKuBuEN3mOjHj+j9GZmVuaWv4xNRHwo+7Kgmxk4dCH/WyDuemDI2cMQIGx5ZaOv+Uz9RQNepfdYqPbzB2/9ekGwAaJ7ElpOuiTooFb7zEQw5Gyejs2TcMgZhpxhJjLRYkcjXv8mgJloQS4gpgoMO4RqsMjNEoSYGADg8XquFgqIs1et0Rm4y8BYqK9rJ+8nrm7//VwY4BDT8oh66w7wdINuY1i36FYDQr+2r5gWRoQBLcxaM71vhGbHtACkGCDEtBp7vJ4rbVhlGvc1g5ujOMWARjlMG3NeQI0xQPj4hG9dzgLeKLMkxRLzbmlBJjUQi5FqDmv/lp9O+LY3mWJAzY7F2JG5PXbBWwaZ9/hc+g3f2lCPW36Xg3nbn7EfAs3X9neMq50AAAAASUVORK5CYII=)}span.runner-state.running{background-image:url(../icons/running.gif)}span.runner-state.false,span.runner-state.stopped,span.runner-state.true{background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAACoAAAAqCAMAAADyHTlpAAAAIGNIUk0AAHomAACAhAAA+gAAAIDoAAB1MAAA6mAAADqYAAAXcJy6UTwAAAAzUExURTxGYTxMaj9FYktZdXSHpT9FYVplamBykExLT4mYtZByMb6gSPrIbO/Sk5OTkw4LBv///4iQZ38AAAAKdFJOUwH4Xfn/K/79yv8b7m9OAAAAAWJLR0QQlbINLAAAAAlwSFlzAAAN1wAADdcBQiibeAAAAAd0SU1FB+AJFQwTJ324eWMAAAIsSURBVDjLjZXtmoQgCIVDSFSy7v9u96DWZO3uM/5oJnvj64Aty2uRr7B8s1iwaP0GjUL0HboqEyn/E8H1KImj+rl/5cKnSzgnYqXuIrDyIxUVaT4DNZRE26vY1/HWRSqpREq4AiKPQP0XBrClnxxX9vgYBkQjcYyEq3rNHGe5mw06TBGVYrZtZiXi3jc5z9XgzlKxWrdtB1yrlUbKHKtLhBCi1W2/1laNyW081AgqbnK/LQEbo/BTN0Qbty3v+wxbFA2vHmGrgsdIa28/Da6mwi//sZH7cSQnj2OwRR9mCaRnZHYcR0dTz22Lty5b15BISs+9dDScKMxCCKYUVu8TkSzROvqxWkbJTIduC2XorIT0+6N0WH/DTpQYfaCZl5QZfzletbdBnLdbPFH0nLfKyP+zTlQqUGiWEUALRJtV2/cXjxJkxKiRF2TPmNGWlpWZdDU8LR/2UbAVCjT9S5rI0vTKc2dRLrXXqoworPRyoa7zICaRXliv65H80quFSjz7RaWMXrXiZGrqiSf16OwlqZZ6lfLUw7tF0vJurVtnDx02Y8069/bKWeM8Lz4xxav/rAA6mHmCfVxwtGDIc5rcZ9/0IDCy1ee1GoYlYztqjuvk3mWGAWSHg8BKKd568C6u5S2EhmaFxgrBtUXoZxDc7dmbalILsLsBLe09HFRHc/gg/XhJ11Hc0CuVwK/D+ubhXaE/VmpWw5foL2fK718FVOGp5p+fGBys6b3/A/dgJEXSAh3eAAAAAElFTkSuQmCC)}span.runner-state.aborted,span.runner-state.error{background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAACoAAAAqCAMAAADyHTlpAAAAIGNIUk0AAHomAACAhAAA+gAAAIDoAAB1MAAA6mAAADqYAAAXcJy6UTwAAAAzUExURTxGYTxMaj9FYktZdT9FYWBykExLT1planSHpYmYtZByMb6gSPrIbO/Sk/8AAA4LBv///y1hUbcAAAAIdFJOUwH4Xfkr/cr+eNcn5wAAAAFiS0dEEJWyDSwAAAAJcEhZcwAADdcAAA3XAUIom3gAAAAHdElNRQfgCRUMAA5e5aCdAAACE0lEQVQ4y41VCZKEMAiUIIQcjv//7TZJHDXubkmVo9FOczRkluVh5BaWN8YGo/UdlOgl1JhI+J8Ivp8UpCRyrh+58OGSHMpCbbEGGU9nfGIWnShQg5JJ24r3E5axFouk+AWoRSB+N2N8kzPHlT0VBoFJdGBkcj9tG3O60gbpVEDkXGqtpeRIETuc4V4N7liKZdu2+gF628pAPvLyEACsn6/VLXscMqsRxDhv2+dqFcTxqRuijaV+JgPWJDyE59I4kVa/DSyK8vAfu/d9V0fu+8BmmWjJYm3uy77vHao93nqNdl2DsuVOmjtUDyhoIQSThnWBMmbJZOR0suZRhtJkQ7PDNfSEmnWkrw2DHeWAQlo0QmJA8UAcv4Ua7Me6QrQGBWtq8sXt84dtDpUGbQ10YfWsazkXiDUlQHRZFbEAfXisWT39XE4oOknDPsqlYpcKAOlXGcVCQjcJUpe17Add0V4DQO+DGKw1S9ZrQpq9CdLcL94DteR78j4QcfLvTQBpy1yoUrOk+SAIESHMtUVvYwjleabxfV4Gskk6+Xf58gVcXdLop4DprbOTtJcxVx9Zv0p2mcRpL0fGgpX4K/+WMTIFP96aeGfepBdaxE6WGBoL9MYudt2J3F2ye7AKujYXioFICBGM6941T4+j8HCytrjP70rzAbte+oHjs/C/mjqrvYaavfrbCMj+oeYfUJ/LX/z/ANqPJNQJtoGtAAAAAElFTkSuQmCC)}div.controller.running>span.running,div.controller.running>span.sparklines,div.controller.wait-input>span.wait-input,div.controller.wait-next>span.sparklines,div.controller.wait-next>span.wait-next{display:inline}div.controller>span{display:none}span.wait-input button{float:right;box-sizing:border-box}span.wait-input span{display:block;overflow:hidden}span.wait-input input{width:100%;box-sizing:border-box}pre.prolog-message{white-space:pre-wrap;padding:2px;margin:0;width:100%}span.output.error-context{display:block;position:relative;padding-left:25px}span.output.error-context:hover{text-decoration:underline}span.output.error-context>span.glyphicon{position:absolute;top:5px;left:5px}a.goto-error:hover{text-decoration:none;outline:#337ab7 solid 2px}pre.msg-information,pre.msg-informational{color:#060;font-style:italic}pre.msg-warning{color:red}pre.msg-error{color:red;font-weight:700}table.prolog-answers{width:100%}table.prolog-answers td{padding:0 5px;border:1px solid #888;vertical-align:top}table.prolog-answers th{padding:0 5px;border:1px solid #888;text-align:center}table.prolog-answers tr:nth-child(odd){background-color:#eee}table.prolog-answers tr:nth-child(even){background-color:#fff}table.prolog-answers tr.projection{border-bottom:2px solid #333}tr.projection th.pl-pvar{color:#800;font-weight:700}tr.projection th.residuals{color:#888;font-weight:400;font-style:italic}.answer-nth{width:2ex;text-align:right}th.answer-nth{color:#888;font-weight:400;font-style:italic}td.answer-nth{color:#060;font-size:80%;font-style:italic;background-color:#eee;vertical-align:top}div.trace-buttons button>span{display:none}div.RIP,div.trace-buttons button{display:inline-block;width:24px;height:24px;background-size:90%;background-position:50% 50%;background-repeat:no-repeat;margin-left:5px}button.nodebug{background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAADAAAAAwCAYAAABXAvmHAAAABmJLR0QA/wD/AP+gvaeTAAAACXBIWXMAAA3XAAAN1wFCKJt4AAAAB3RJTUUH3wQBDQAOjeB7qwAABLlJREFUaN7tWltMHGUU/v7ZYSmXBbpbEDXYGi6VCmpo+2BMDETJQpvyYBVvNGmIIabaGH1Aa3wg6UubGH1Qa9Rq2jRdEqlPmBhSG0LUxhZptlDKStGEWIHtUsp1F3b3P8cHdpYBamEH9kLSk5xkM5OZnG/O951z/pMF7lt8TUT6wNFzI+8w0KAAZz56MffYRgTgBZACAEKIE8GenMNNTYLiBUAx8EyK9oOZD6Fk+EzDV5y0kQBABwAcxGvZluG2xm89lg0FgJkhiUHEYJIVSpLvwpHTN20bAoAW/BaLAkkEIoaUvNsvA22Hv7uRndAAmAEKffmcTBUP2ZJCmSBIyTuFX7l06IuBgoQFQETzAcv5LFjTTdiabQYxQtfoUWb5S8NnfaUJCUDjvUYdIkZWugn5DyaDodEJuRRER/2nfU8nYAYYUoYCJYTdkqqiKC9Nn6XNMkDn6473VCYWAMnhL7/U0zeZsGNbGhQFWpbSSHLry0edLyQQhWgZhfSemmxCaX4GVJMGgpOJ+Pv9TVfqE4dCmoj57p5sVvBkYRbMZhNIEiSxSUo+ue/DzncTAkAoqP+lEhHDnCRQtj0TaSkmTTeCiD+xN146lhAUWo2rJoGyYisy0tVw5ljS+8+9d/HzpiZW4ibicOMKBXUvFwIoK7bClmXW95C32sd+O13e1K7GqQ8QpORVZ0IAKCu24QFrSrgAyCDV+UeUH8oPtm+Kj4iX9IGVnBh4qtiKvNy0cBYlUc20iX96pv5XSwwBkI5GkTkzUFpkRf4jGQt0Ii6flr4LO19t3xLTUYIiEPNiEIzHCzajpNCqzU4g4t0+Eegoeqn14RiJmMJUMuoFWzPxxHbb/GguGcy0Q1WTfi55pS0vNp1YsqEM6L1wWyZ2leSED+YMPEaCv4kkHtW4iOeBrNWIF7+DBYuoA1ioImsD4Pr7Drpdo9AwCMClkPJGVAHIJQI2dCQFw3l9FAODE/rLF83JyXudpyrGo5sB3RwkDWyDmIA/em/hn6Ep/XKqTVXFfuepiplI36caLaNS0jL+rubZzm43Rm7p4xQtIjhR191c6zeSTYMijpxCQUm47HRj9I5Pf/lkX3DiTbTUSqM6iomI/QHC5asjmJic01ebj12OqkZArKkSGKDQ4g68ks35JTqvujE149dvZD9wOaqPr8c4bUDEq+8D3tkgunrc8PqC4cchxNt9DvuX63WgMVxGpbw3hWa8AVzp9WBuLhx8gBkHXc12x3qeyAxoYGUKTU374ewbRSCgaVP4WEGt66z9x/U+ExurQlI7kS2/Pz45i2t/3oZcuDnJkDWus3s6orGVMN4H7pKB2+Oz6P9rTB+8h4Wodjn2dEVrL2RQxMv7gGfMi4HBcZBkbbK8SRCV/Q67K5qbOcMa0IvY7ZnB4NBkOHgAN4SQlf2OvYPR3o0appAGZMg9gyH3lD4bThPUqmuOKncsttMGRTwf/L/uGQwvDr4rEKTqvpbnPYiRKWsR8YgueAG0pU4Hnh1o2ROz4A2eiWnRYmthopys6Wrd50WMzdhuNCRiABACjlSL7fXeFmPjcDwo5CPS6rw4cb3o9wNdX+8KIE5mZBo9AsYBhjjnarbH/a8G9y3e9h/uU+EcypgobwAAAABJRU5ErkJggg==)}button.continue{background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAADAAAAAwCAYAAABXAvmHAAAABmJLR0QA/wD/AP+gvaeTAAAACXBIWXMAAA3XAAAN1wFCKJt4AAAAB3RJTUUH3wQBDDMd/Pc1cgAABW9JREFUaN7tWV1sFFUU/s7sdLZl2+2P2NJfWloDEQIaYhPEhESJBiSBRMODPy+mkYjRBx/EFNE+SFIxGiHhzajAA0GUJ30w+CAqQlECRIEEiKVLW1pK45b+7e7M3M+H6ZRZdpew7SysSU8ymUzunXvvN+ec73z3DjBnczZn/2sTABg/8Fx1QNOLACAWd5viGV6JQTP1WyWv/zwsAj5wAKP7nt8pgnaAIAmAAAlCTd2dZ6ddwdOPIIcJDoM8RbGP2RI4Vtl24sp9BTC2f30EQH2Wi/e0qzv64aTA/rxiIPyddPxs5R7AvnV9BGoAAkbICaqUxSffYcWhrBigrDT9lNuvRyht87ee+SnHIbSuD2ANSBgrXnZA3KPRToDxUdgjEdi3IrCGL0FZca+HFBQ/ebjA2CFbTpu5AKAnhY1SgLLvHb0EIIVl0ArLUFC1HGyKwRw4g3hvF5Q5BpAaRW27YU0u5jd4UTbD9huA5o15wAY480sCBTBqW1G8cguMymW3xyU3DQ4u2c8OaL4DSEpYZftyiRZAUct6FNav9ubOS9crWt7OkQemwogKpO3bFaxfjYKq5dMsJsBHvXta6nzNAS+LJK78CIikoUo67KQVQHQD0Iughaqgh2sgRvFdJyhqWgt7tA/W2ABAhgJQ7wLwzRMS/fLpXgFr753nvVQJ6KUNMGpbEQhVZpzEGunB6N8H3XGi1UUVlX6xkiaCozNbvNNuRrsxfv4QYn1dGZNbD9dBKyp3xynrnxha41sIhUMPtUXHh3aLZQfEI5EEFkyZ5ksIqQlYbhPlAi4h+STAtSA1QiF+7XcIgOCCx9NOVFC6CPbETaeikxsB+FLgdNl82AZwdiYv39i7tIXAXpDPAsTktePQSxugFZalTlRWD/afdDwJLvOPhWZhlW+ev1KpF24geYx0QirW/2daatX0kDdMF+QFAACQLadNEO+5VGlGuwFaqUVOL/TmWHXeAACAqrcudpEcAAiaE1CTI6ke0AJetVuaVwCcjY3qdtlLmaMZGMkrW3wTcz4VFKpRBUeKKzsOMlW3JcmWfAOgRAjl1BNRVnpVm7TPyDMA7uIdnldOyKR44HZRzD8ASdtOldEDt6k0zwB45YiratODdORInnpgKjxsO60H7hSCeZYDBMSN8fQ5kCQEHxSA7q8aC40R+VSgWknKlLaBIh6RaZ630iexR+1e7QwfBW0ocAoPJ6CsnYveN0/lFEAwqr0AUVvvPGoRb5FSzHA4kCTV16ZIdZE6ACtzWolt4V+kSmQ6yUPAgFZYknaLaZTU3mWfQYA4N6Oz0Wytd3fDM7DVtwDL3MUHSxtghBciUDAPEjAyJro1+S+seBSj/X+AKuE5NMOBuJVoW9qBRM4BAEBkV32zptk/UNRiNyyC4QaEKpcBktmx5sQQopFfQDvuLl4B8k7z9vjuGZ9Oz9SufVZXAds8QuEaNxz0ovkoqV4J0VLTK3Yr4nx5Wu7iJyB4tbk9cWRWx+uzsct7WoJGPPqFAK+4PK8ZxQjXtCLgnNgDAMaHL2J86IK3mA1qgo1N7WbXrP8PzL4KQyK75n8IsT9wqVULBFFS/QQCwWKMDZ5DbKTHm7AXAkrb0Lgj1u3LDw6/rLuz/A0RtQekThCiadCNMBITN70a6Lhlxjct7sBNX2R80pORZY1PSMoHuNoZXkfwEKhKUnmeB7VE4rWmDsS87zz12IWs5v3t7KOSMwAA8E9naAXI70HWTQs8cGdze2JHut9SjXXXs5r3am91bgEAQOTjeTW2UocV2UKqbS3bza8zjjOLeZMWsLA6ktVAPdcb/MkhvwD46YH7BSCp2qxq/DWrcU5c8oe9Vi3Mct7LmLM588v+A+5od3b4azuuAAAAAElFTkSuQmCC)}button.skip{background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAADAAAAAwCAYAAABXAvmHAAAABmJLR0QA/wD/AP+gvaeTAAAACXBIWXMAAA3XAAAN1wFCKJt4AAAAB3RJTUUH3wQBDDc5pJgUpwAABxRJREFUaN7tWWtsHFcV/u7MeNeveG0H2/WTxE4opVQqfamNWsEPVEoiixIwoFaVeKhQgRTSVlSQFLF/SoRQhBASUvkB6kMNWKWKVIkiNUUJCBJC+kpUoVhO7Tp27KS2d73P2dmZ8/FjPbuz3hnHXm9aKvlKI69n7s75zv3O+c65d4HNsTk2x0d6qGq+xNG7GuLpSJeirZU/MX3na/lsYst3X19QCvxQHIj/fs+gptvfUMRegoMg2wCCIEACIEhZ/lv4H1z5nARkgeQClJxW5AnHUSc6f/DG+DVzIPnsnhtAeQrglysArQ88ACk9L5/7bxK/6ni/7c8qetyuiQMcHdHTuewhivMoQKMCkKZDGQ2AKgHxB19wFbYJyWcBOoFzSZmCyHe69v332IYcuDI60txopl8gOVw0oggtsg361h1QkV4ovb4quulYYC4BO/4enKX3kF8YA20ThLiLIxD5ZWe4+afqe6/n1+0AR0dCaTNzjJR7XPCqpRdG3x1QDe01VxDaJqzZMzCnT4JWysvM0a7rxr6qvgZnzQ6QUJnn9vxJKCNunOp9t0PvuPGaSyHtHDLjf4F1+e1iWJF8oTs2/pCKQlb7ru5++NHQ7m+SPOCuvN7zGegdnypQe40vpTSEtl4PgMgvTRbugTclGyPxw6/ET12VAT493Jiqt8cA9oKEatsGY2DXh1KY0mMvw5p7082LtGj5T/btm5kOmm8AQLLe3q+WwbOuHkbvrcuKEUC5lYEkp+Gkr4BWBnRygJ0vSOWy9njVhlBQdWEoownGlh7obUPQ6vyFoHHoC3BSM7CTsyDYpBz9CQD7AhkgoVLPfnESlAGCMHpuhdY+6A9cLOSnz8BZHAfprFXnS1K5rDZKDyHcdxfC3bf42rGXJrF07nn3/fHZxs7O2wJUScs8c+8tLnjoIWitA4XVX3nZWVhjr8BZGNsQeIAQ20R28m8wp/7ha8to6Yde3+a+q7U7M/vZwBAS4H7XiNbcBVDg17Hkp09DsjFvQTsulFeVkvMCNQ9HUuWpZRc/CRiGSCc03ETh1wHeCBLZmVMwWrfBaOqqsBdq24FMZr7gsOBLAI755wDV7UChFVDNHYXVrYj5FOzYhAueUHiw/eFTR6rI0aOMfu7Q5fbZlwgOQ4jc3BvQB++tBBYZAGZOFhZL8dNBL9SoZMjtbZTRBIhTcTmxSU8o8Gj7wyePVKsyKnrcVoIn3XCyYhd8bWp1TaUQFLku0AGQLS44peu+MemYi8X4VcKXNiqVXfvPnwUYIwTMZ0ErWWFTGQ3LiyYg2B3MABguS0if1YCZLD5XdN6pSfWFvOuusJhLlQxougseICPBdcDbEtMBqHzkM19UG8CI1aZ/YMJlXhwTul/ueTrgVQpZqZ8HHdDXAacolbaWz9WIAauAi6DYvuJRLtUBDpRtRsQJ2CJ4db5mm0EW3+uGjh8Ha2OARQZ8Q8hlCKx2G736orjJW2GXHruBDJSqZiADXipVjRwQj11KIANXDSFvyWcAA2uhshoGwOUKxIAcWFMI0ZPtAQyUkryGDhTtSiADLDs0CAohT5OFVRhwWVLI1CoDSjovEtC+exTy6nXAXQ1/OWOVDExEt9WHWp3DEN5BBQVxVU920psDvklcYv7dQ42vFvwQd8uZ0cinDG9L7J9IKLbChKxbg8IR+ysi+D5AQOhtD8qZD0ri0uJ93psTBRyqX/P286TjexXiVapiwFE4B9AqAVkBXgtBC0d87YZa+nwOyEoYqPC2UaHHAn8q3TnrTIH+/dNnpw/37ib4IiitLqBw5OMIt26HXtcApRm+DET67oa9NQbbjCFx6TRAy/v4edliPaKVFQu/nVjF7mv9o+/xmdfoOLcJeN59lxmfQC52AUppq9gVUCwkZ/8DiuXRX7V/6KD10M59yGllxcKvE/X0QRupAwNPXLmgaeYugCfcd5lLE0hc/Bdo53ztmvEJxCZegzjF9isDhZGhg7lf+7YS2blzvnvYsmq9gdH/WGLxUrRnt91kPkdyL0lYmctYuvh3tPTcCc0IF+dmY+NIzL0FT0wvakr2bj9gnyjfD5DWahvwlRv0XF15IK539EQvZfrTiyMkD7s6nzdjiE0dh23GQbGRvPwWEnNvesGPK1G7VoIHAHXltzcfUODPCIauAl5APtP9w/Fve85SG9DQtmZlVcO/K5OAiUPNjyiF35A0CEJpOupCEeQy73vCVf3Tzufuvz6K+Zr9QrOiy1vzSLz8QEfL8JH5ciea7iNkFMQWH6n8o5a3vrU9GvDTDwDtAz03TKYqbm3/SfqvEO1ugBe94En8fPCA9cBq4ItHi9WOe24440zNd+vr8MD37uDB9NmpXzTembedUSjuBPDjHQfzf8CT1/5gfF3H0ImnP/GxWiP4QEMo5RNCHykHHC0l2Byb4/9r/A9GxF3/Bu0ZYwAAAABJRU5ErkJggg==)}button.up{background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAADAAAAAwCAYAAABXAvmHAAAABmJLR0QA/wD/AP+gvaeTAAAACXBIWXMAAA3XAAAN1wFCKJt4AAAAB3RJTUUH3wQBDDYM6zDhxQAABQZJREFUaN7tWW1oVWUc/z3n3JdtXudUzBfyZcuRaUVSmbVerDQLC0FIkCAR+1YIUhLNivslqm9ClrhR2ZQopPrSlyAQMZGQymXZjERN0d07d9e2u3nOPef5//pwPHdznqsbe+buwD8cuFye8zy/3///+7889wJlZp3Nj6RzTcv7O3c/2ExC3Wi9VW4EFGUrqStJeaVj133vTTgCpI6TAlID0G9lP1q8aYIRCMCTGhSBQJrbd9Y/P5EiUARPaoBiU8uX53bU3hspufEEm/14RcpOXK6xPUm4AAAHCviTIhWkhmUnob18SOQUtL98zhsXLo0Lgb4vVi7VmquE3lMk7yd1DSixwOMS5XlU3bUOfW3fQnwHpIZQDuve5Mra9Bkn3Dc21sDzn69+VqAbfS2PBSBZBHg98KSGshJILdmA7tZPQQpA3aCqej4j8ZJS4JgS6Nz3XHXCkxaBrOUQsCFAKAuIVUApACIABQoDa2KTZ8GqmIZU/QvoafsmIAVuOPtB9T9Az7tjJqHuvasXWoLvKXJn6F0oC/bUOljVc2CnZgGJFJQ1fP/1tO1H/9mDoGiQQtLfWNfo7DVOgC3PTMqL+pmUJaHX7RmLEJ+9FIhXjmJnQdcvTXCyv4eSc6nkaeNltFfUJyF4QCFe+zjitz8E2AlA9CgeYso9G6Hik640OSQVrTeN5kBfy6oHtJaXQ9nE5zXAnjIfoBjZ//L5Q9Bu1+AiesAoAdFqK+mD1LBr5sOeugAIvDVqczqO47+2/YO/2lfX6O4wRiDf/PRMTf/FsFTaMxYFob9evoiGOF3QTi5ITt8BKVBKITl9EVS8CgBQ6DmHXOsegAzegzroeu5mpUBjBHxLngAlTgpU1TSoZHWo1YhxwYd7/iiczK+QQt81/QAU2JUzMH3ZFminC52/7Qa1G75+Mum56xamUTDaBwhpCOu7Pem2krqn5yB/8jv4+YtgRDMDBRQNL38BLPQhd6wZUugNNd8hgjVz08iZ78SU5SEAq3JaSfn0n/5xKPgsoY8R0g3qbopsJkWRGrnje+Dl24s5LEqvrX/HPzV4P3MRoJ4ZRsCKV0Umr+7PopD7OwQvQv3a3LntTWo9iotPv5/aRGqb1HC7ilhFERvrt/tHhu5pMgJTQznAsiMJuJfaBo0TbJn3evuuUuP0EGuse7uwf8zuA0yviJF6MikggioS1Yz83otFzQv9r0rdB64el1XTHdsLH5Y620gEMnW5ZKw/roKZR4EkEAyLV1eqy5eKEdDC1pL1YODDD/967qs35Uo5eCQG9bWP+BDfDdfJgm0dmWj06vCVD630CuufTMO/3rkxowREACWRFYjiIezSgPSH8/xQSyXcNflCxTLXd44uSSN/o3PNEMgArLxyCYGKHh+0N7jOe6W2mrUNfYBzYLhHG40AKIFbo5oYpdikaGi4M11GEY7QjJIQdRE8DQ145nOAOqgLUQCHjgzlSUCC4hdJwDx4gwQyIJMDEYiag8Q8+DGMgERKaCzMIIGB5IzyNMufgB7oAyUkVPYEgkRFySpU1gTCJgWlSuQAyzwCxQ47YSUkxW6b+etr3CwzMk73JjM+qTn8SsNCWRGo3wIX9HcCGA6DApTaYYrAVT/uPnr3iRFl2k9/LFamBDhC2CoyB85nazAe1rD4+IjWHz5RIonPZGePCwGKb0ZCownleEmo7P5mHVUfeLj20IhePnIat+yWTXT7H9J2ChlDGcHsAAAAAElFTkSuQmCC)}button.retry{background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAADAAAAAwCAYAAABXAvmHAAAABmJLR0QA/wD/AP+gvaeTAAAACXBIWXMAAA3XAAAN1wFCKJt4AAAAB3RJTUUH3wQBDDgagWd5GgAAB1NJREFUaN7tmVtsHGcVx3/nm9n1+hLHzj2NY9eNMWqFBK1DUAJSIhRAQqqoCjU0IkUgQXkBBVUUpebBCBR4qaJGQmpA3ITKLShUsgJ9KWoVKanS0kJL1KYkcZr6Ejtq1vb6speZ7/AwsxfbMxvb2QQq5ZPGs96dnXP+5/zP/5z5Fm6v2+v2el8vuRk3VUUyP+tZaxP1zdFXpOZfL65taZwck97Tc7ccwPhP7+tyHN2tIrtRs0NE1oJZKyICAiJIeAZBSmfDvM+D12lBLqpw3PruH1q+duLiTQGg/Xvcq+vTnxfhO4h8rNKx8mtTfm95ICqv/Qti+lY9cuLNmgEYO3L3Xoz5hYhpj3MMcTCJenBToWNUASGggnpziPWjQHhinMONdfUHpfeYv2IAerQnMZ6b/iHGfBfEBEYM4qZIrO3GWd2B29KB1DUjTnJlteNn0clh/PfOYycvIToP8MBsqnHfht5j08sGoH/CGbvS/WdEHihGTZJNpNp2kty8HXFTtReCuWt4Q2fQqeEKEOZkY6phr/Qeyy8ZgPZjRlu7fisi+4ppTW78MA1dn0Xcupsuk/7Vs/hDL5fqy4g51rD/xBdF0CUBGDly5wFR53CRm/Udu6nv2HNLtd4f/zf+yGuVdPpq0yN//fV1AQwd2dJmbOItRBoFQ3LTvTR23/8/aVje5VNo+lIRxHBT1u2WRwdm3aoa6zuPq2ijKDirNtCw7TOgfuS1tpDFT1/Ay4yg3gxayBFkeYHEAmDATSBOHZJswGncgFnVhiQbYn1xtvRQmL6CFLIgbMmkvAPAoVgArxztSTA7vh8FFWi485OBcbsYQG70VXJDp1E/T1GdYiU2ok948hYiDs6aLhJt2xGTjNB7wV1/D97IPxAFEXlUlR+bOACbZ0d3q2oLKE6qFbd5axD9BUf28knmLv0d62UBBVUUG56D/0HR8Fx+bcvvqaLq47/3Nvm3/wbeXKQt09IOTjK8r22f/c2n74vNgLV8TkRRhWRrV2TkvZkx5oZfQgKmoMpZMfwRq2+okXEDucBBgESApQjCdZoM/jqr5oNGzKdQ9qiAnUtTGDpDYuvOSL9M00bsxGVUwMID8TUg+qGQwrir29EI7ueuvArWoiKIysDGa5selP4XvBXU6KFrP9/5MKrPqCBeehBnwz1IsmmxW03rYeKdMCjmo7EUwtpNRQqYRGOQgQVHPn2hRAGxfH+FzgOw5uunf6/os0Xq+elLkTbFbQwohKJit8UCUHQzalEUcesX8VHzGbQwF/AdTW88cO71G57trR4vBsTPXousA3GcyvpqdqsM9atVQNRijLOoBmx2MgCnoGIv1kLrRf2zVp1AuLKZyLorFz6oUFelD5QuitR+62eDSAiIMlWbduWmwUfVoLYQ3XPUR9UGo7iCG58ADSKhRBawWq8CpOZr0m1NIScqiFjU+pF2A1BaAlE1A6phH4pIJdYvg8RoDefQwC72unZVbXUA4fNtbCrLIG0tB+nQrl2C3aVQKGZ8QINuiwA19L9MXY3NQNGuVquBSpSRNaBeSYWCP7WmkMbWQNlu1QwERRKMLXEZsKiY4NGvhnsyhPyuloFA/eR6GSjKlR85LAWRsFgxNfJ+FiURJlSr1kCgfhb34o8SO6xIn4g0BNO6CXhdGQmNr4Gw2e0aenLzKyBgDKIoRs7kJ5zHOvsvZZebgeCeGmu3UuJdkKcF7g3ac6goKsUGFRbp9SJBM2p7EIOEwx2W7XWrvVPAM8urAIuoCUaUOAphUTWIgFHhX/NpUzGjoySb21D1Fx2mbjWY5Lxri7NTqL15X3hjJTUQPE8QaTc4ys8Trl2V/6bJJF3gyyUdlgTNd+zATbXi1rdGRsIYl9a79uIX5shNDJKbfKdIJ1TMhKh8YeuBodeXWQKQCLMaV8QL+o/5wLfJbevL7wc5UFR0tXkyoy+jNh9y3Y+eDMWQS18gOzFYyoRFz6nvb297bPj5lfaB4r3i7FY+2ZXkY1tf7imEh8I4YP0c6cHnA+ci5nL1cky9e4rs5GAl9V40Jrur/fHxCzfWBwKKRNktjhJFEIsEfPCQu9uqOQ6sCclC86aPUN/aVa4jL8fUyEt4uanSQ7qIHHdnUvvv6B+ZXanrVw/fvdl3/JHFe62xGwWTiwS88wnvRbGyCzgfusvUldfIjP0TtR5edoL05RcoZNMBT4OIPbl15tpDN+I8QC6h+ciNgPiNgnxsCz3Xzzo3Ufcs6MeLGxt1Desp5CdR6yNBBDxVvtV5cPrpeSQY+EbDkr2eS6v0Hiv9sDH6VNcvEfmKhBvIVTKRV+QHVWeAwX5SNpH8FfCl0u5M6WZkBNPbeXDmucrvTA08vK75/t9dXeaz2IpnkaozQGc/2bueyO9T5dCCPvEu1nxiofMAZKZv6Zaju4TYKOT7LhxKnAd+gsp/XMf0tn9vZiT6Gxk61g8v2YH2daP+yTf/j341nDravS4U8WUcK1+m1gCmbzGFag7AN9OW2+v2ev+s/wKIypfbke4fXgAAAABJRU5ErkJggg==)}button.abort{background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAADAAAAAwCAYAAABXAvmHAAAABmJLR0QA/wD/AP+gvaeTAAAACXBIWXMAAA3XAAAN1wFCKJt4AAAAB3RJTUUH3wQBDTcgwTHWUAAABeFJREFUaN7tWU1sVFUU/s69b+Z1eJ15pbUF6gCagIFEWFgXXRhRSNCVisRuXECFDRsSY4IhcdHERGITQgKJuoBUVyaQKK40xhYlXbCgmyaKEgP0Jy0ghb5pp/P33j0u3kz72s5M3512xEXPcnLn3u875zv3nnMesG7r9nTs8nuQ/4e9qJY/OX0HXgewy+7u/3K14PlsZ2y2pfEIg/9KHO2/VncCTt+BV5nVBYCaobjXdjIX6aMbmVrBO3bsOASdEkRJBvbZ3f3X60agBJ5I7AUAZh6vlUQQPBElSz8DeE2HhAi7MHVp/6EgeAAgoiQEnXLs2HE+2xlbJXgAIGZ1IXVp/6E1JZC6tP+QIu4pgadYC8hqq4lEOfBktYFiLcX9xF5F3BOWBOnKhho3w2jvAEkT7uggPGcMZJih5FQOvLC3w2jvAHs5uBND4Nn70JGT0JFNCbxMJCGsVhjbXoFseSFUJKqBF1YrZCLpO6Zxs5acSNfzMpFctE6l/4E7MQTljKBSYq8EPmhealwrEhRK8xXAhyEBAGHBVyLBrIYFU0/i2MD3KxKY7tv3Jlh8HkxYY2tnRfDVSJCrzjEBkOLDsOAXkRi7Ac5MzZMAqY+bun/7KbjOWI5EbARR80KWSJA0V77OrFYY7R1wAXhTt0GGmUREnhXki4A1wAPwzxTBCoOaJUWeWzGJm45d+5aIPpvn44zBHR0EWAHCqE4ivgXRHQch7a2AmwMVwSs3B2G1hQZfiianHy5Ikri3ccPsN0vXli2izry/6fdswXgAxh6SRoILaai5KZAZB0WtKpe8AmQEsmUnOD0JlXkMVh6kvRXRXW+DGpr8NZpSBHGvbWUuUtfy67niLcSXO2NOOnYcHD75fKkwQACnH8GdGPJ1qun5sOBXfMi0SATAU3FblXV8aTXYdQEf6iXWIUFF0TPrVaW1gg9VC1HXjYxtZS6CuJeZx/3EHvHlEUjsmsALY1XgtcrpspFIbINs74BobJ2XzX/lee1yelkkmOFNj8CdHAKnHz0V8FoEgiSI1TlmngYB7Iz6QIoJGwp81lkMXqlpQJ3TBa9NoERCSGNOSNEkiMBuDpxzIMx4+EPNODjnAJ7/2JEQTUQyowteu6XUqSrDSKgwcRPKGQEBYEZN7alWBGZbGo8IQ5wXREkulgfRHQch4lv0vEaATGyBueMNSGsT2M2DiJIkxflUs3V0zSOwlp4vvXrM/tUbpp9YFYF6gtdpimqWUM2yEYb/0BUfO6ISaFoEPljFCqsN7Oa05ET18nzJqwvF3DPLPK/T2VWKhKiX593RQXhTt6Ee34Y3NggwVwVfaySoXp4PeBEgQCa2w3j25drL6gqRkEunxMkXdx6GoJ7g0CmS7KzxYDUNIEtEDZxLgQtzoAa7elMEgKIWqMGGykwBhTSIKAHCnlyDMfaSee/WlT/AZSXUdQWekOK+KI37mIFcyj9QRkPLhkp3vZCnifhTZoyj2CuHak9l1D8zlypKz587kRD3u67Aq9pSnrl6997pt54fZvBuIrEJyoVKPwRFYhBmorznZx+gMDIINTMBEgaYeZzBnySsuT4z6t7MFYyMTnvqOSMojA6Cs9MAUXGsghP2BwM/ag22APwKgOAVQGYc0d3vgja0AF5+wfNeHvk/f4DnjEEYZqkjOxE/+stXS/Y7AeALAGA3N98nQ0YB5c57nuemkL/1HTg3AzIiYK4+2Kp4C9nd/ddJ8WFmNQwZAbtZ5O8OwHtyZ8HzM5PI//2zHyHDhGIeV6xOlpseJKz01wx1kpnHyTCh0g/9/85MLnj+yR3k7w6A3SwgI1BKDZPiw9Xmoyu+xJWmdCRN7Xq+Wnu6dLhbbRqnXQuVG69DyGVzmzD1fDkSZLUByls0hQsDXqucXpQTHJg+VNB8iP3mc6I0uiNBK2p+1Z+YSiSo+O9awJcjQQRt8Nr9QDCxqyVsWAsmdpiEXZOvlPMTbCU22vHM1VrawGU5MRN7B0I9WTp5rqut5YfudVu3p2j/AkT4owo7DZieAAAAAElFTkSuQmCC)}div.RIP{background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAACAAAAAgCAMAAABEpIrGAAAAIGNIUk0AAHomAACAhAAA+gAAAIDoAAB1MAAA6mAAADqYAAAXcJy6UTwAAAAzUExURQAAAAUHAmNlaKSkpXtpZllZWVx9LsHLo9bX2Wx9jpazUak9Lu3s797g33SZKnybRP///5NI/qoAAAAHdFJOUwVE/v+8OP47SgHcAAAAAWJLR0QQlbINLAAAAAlwSFlzAAALEwAACxMBAJqcGAAAAAd0SU1FB+AJFQwBEyT4/QUAAAFbSURBVDjLdVKBooMgCGxggQj2/3/7DnNb7m2kdspxgLVtN3sQw8r2y4glCaw/KAW+WivRD5EHK1trrTSqun8TcNWWjFYr0zcBD1FuxtyQ5NO9K2oTlYYyCDmYZcnC6u5wqzAJt1Kx9ZvKHsivWtu0wqLht16QXjULuGwnTv5Ngl2H5vSPDCErocAq7mnHq1IplAqPO4E0qOCqK26aIkrhVYGSgDAqAeyJF4Lj0C/SIACvNcBBWXtUyCeuHEsNUyGdUKm+tpmfgWo4ZtScSPN5D3FFP6f/J7wMPh8CH10oDq8xF12LRKhex8Od1FhT4GNkAs2RD7Yu7y7s6IfNGq5CjuPobwU7JaIboqz3nqTTQqy/auhiZgJfN5Hk9DxJlP/dfp7d8jklh2GRwR5BEEkwouY71wQ2ECrsUICN5WZznynyjS7GGDg7mLsDCjd7bmb3LwQ8xjbXx/bG2x+HDRcuxXGCugAAAABJRU5ErkJggg==)}span.depth{display:inline-block;font-weight:700;background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAAUAAAAUCAYAAABF5ffbAAAABmJLR0QA/wD/AP+gvaeTAAAACXBIWXMAAAsTAAALEwEAmpwYAAAAB3RJTUUH3wQBDjQRuYQ78AAAABJ0RVh0Q29tbWVudABEZXB0aCBtYXNrQcBmawAAABhJREFUGNNjYEAD7Wdr/zMxYAGjggMlCACJuAL3jmFt7AAAAABJRU5ErkJggg==)}span.port{font-weight:700;padding-right:.5ex;margin-right:.5ex;background-color:#ccf;display:inline-block;width:11ex;text-align:right;border-radius:5px}span.port.fail{color:red}span.port.redo{color:#ff0}span.port.exit{color:#0c0}span.port.exception{color:#f0f}div.prolog-exception{color:red;font-size:80%;margin-left:5em}div.controller.running>span.sparklines{margin-left:.5em}.jqstooltip{-webkit-box-sizing:content-box;-moz-box-sizing:content-box;box-sizing:content-box}div.render-multi{position:relative;vertical-align:top;background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAABQAAAATCAQAAAA6heU+AAAAAmJLR0QA/4ePzL8AAAAJcEhZcwAAEMQAABDEAbRyZ/IAAAAHdElNRQfeCg8LIivxaI+JAAABT0lEQVQoz33SsW5SYRgG4AchbSkcYrVpo6bGoXFydvMK3HsJLt6Ct+AFeBVunVx0cjFODvofqyDQFDVttef8cg6IA4SkFXjX70ned/gqk4kV+SUVnGs8rayC54KA/e7DvdpydiZIJXbEJyyFp4IjW27IFG+Xwp9SR266LhM/PT5dAn9IfbGtJROtP2ch/C711bZELmrYOFwIB1JtOxpyfzQl1n4vgANBx65NuaGmlsR69h88EXTcUpcpNLQkknJ3dAUeS327wlr+fpxe57Av6F1iLYmxOLgEe4K+2zZkitm2xFgumsOJrs/67liTGc4qm8YyUbw7gxNdwbE9NZlixhKlXBTl+1NYaU9SPfdU5Ubz0inL5aJya3h2oBa03XdNZqzZaR5uvq5/mFyUcVSUo0JRLerlxQFqwQPVN/FF+T4Jj0YL32ial8/eJfDK6vwDMhCTheu9OHEAAAAASUVORK5CYII=);background-size:15px;background-repeat:no-repeat}#render-select{position:absolute;background-color:#fff;padding:5px 0 5px 20px;border:1px solid #000;border-radius:5px;box-shadow:5px 5px 5px #888;z-index:500;white-space:nowrap}.render-selecting{outline:#800 solid 1px}.render-multi-active{position:absolute;left:0;top:0;width:20px;height:20px}div.render-item a{float:right;padding:0 10px}div.render-error{display:inline-block}div.render-error span.error{color:red}pre.console{padding:0 9px;border:0;margin:0}span.format{white-space:pre;font-family:Menlo,Monaco,Consolas,"Courier New",monospace}a.download{margin-right:5px}a.download span.glyphicon{margin-left:1ex}.render-table{border:2px solid #333}.render-table td{padding:0 5px;border:1px solid #888}.render-table th{padding:0 5px;border:1px solid #888;text-align:center}.render-table tr:nth-child(odd){background-color:#eee}.render-table tr:nth-child(even){background-color:#fff}.render-table tr.hrow{border-bottom:2px solid #333}.render-code-list{color:#040;font-style:italic}.render-ellipsis{colour:#00f;padding:0 5px}.render-svg-tree{padding:5px;display:inline-block}.render-svg-tree svg text{padding:.5em .2em}.render-svg-tree svg g.collapsed g text{padding:0 .5ex}.render-svg-tree svg polyline{fill:none}.render-svg-tree g.noleaf text{font-weight:700;fill:#00f}.render-svg-tree g.leaf text{font-weight:400;fill:#000}.render-C3{display:inline-block}.answer svg{vertical-align:top}.render-graphviz{display:inline-block}div.R.svg svg{overflow:visible}.fold{display:none}.pl-ellipsis,.pl-functor:hover,.pl-infix:hover{color:#00f;text-decoration:underline}.pl-ovar{color:#800;font-weight:700}.pl-anon{color:#800}.pl-avar{color:#888}.pl-var{color:#800}.pl-atom{color:#762}.pl-functor{color:#000;font-style:italic}.pl-comment{color:#060;font-style:italic}span.diff-tags{margin-left:2em}.diff-tag{border:1px solid #ddd;padding:0 4px;margin-left:2px;border-radius:5px;background-color:#e1edff}.diff-tag.added{color:green}.diff-tag.deleted{text-decoration:line-through;color:red}pre.udiff .udiff-del{color:red}pre.udiff .udiff-add{color:green}/*! jQuery UI - v1.12.1 - 2016-09-14
-* http://jqueryui.com
-* Includes: core.css, accordion.css, autocomplete.css, menu.css, button.css, controlgroup.css, checkboxradio.css, datepicker.css, dialog.css, draggable.css, resizable.css, progressbar.css, selectable.css, selectmenu.css, slider.css, sortable.css, spinner.css, tabs.css, tooltip.css, theme.css
-* To view and modify this theme, visit http://jqueryui.com/themeroller/?ffDefault=Verdana%2CArial%2Csans-serif&fwDefault=normal&fsDefault=1.1em&cornerRadius=4px&bgColorHeader=cccccc&bgTextureHeader=highlight_soft&bgImgOpacityHeader=75&borderColorHeader=aaaaaa&fcHeader=222222&iconColorHeader=222222&bgColorContent=ffffff&bgTextureContent=flat&bgImgOpacityContent=75&borderColorContent=aaaaaa&fcContent=222222&iconColorContent=222222&bgColorDefault=e6e6e6&bgTextureDefault=glass&bgImgOpacityDefault=75&borderColorDefault=d3d3d3&fcDefault=555555&iconColorDefault=888888&bgColorHover=dadada&bgTextureHover=glass&bgImgOpacityHover=75&borderColorHover=999999&fcHover=212121&iconColorHover=454545&bgColorActive=ffffff&bgTextureActive=glass&bgImgOpacityActive=65&borderColorActive=aaaaaa&fcActive=212121&iconColorActive=454545&bgColorHighlight=fbf9ee&bgTextureHighlight=glass&bgImgOpacityHighlight=55&borderColorHighlight=fcefa1&fcHighlight=363636&iconColorHighlight=2e83ff&bgColorError=fef1ec&bgTextureError=glass&bgImgOpacityError=95&borderColorError=cd0a0a&fcError=cd0a0a&iconColorError=cd0a0a&bgColorOverlay=aaaaaa&bgTextureOverlay=flat&bgImgOpacityOverlay=0&opacityOverlay=30&bgColorShadow=aaaaaa&bgTextureShadow=flat&bgImgOpacityShadow=0&opacityShadow=30&thicknessShadow=8px&offsetTopShadow=-8px&offsetLeftShadow=-8px&cornerRadiusShadow=8px
-* Copyright jQuery Foundation and other contributors; Licensed MIT */.ui-helper-hidden{display:none}.ui-helper-hidden-accessible{border:0;clip:rect(0 0 0 0);height:1px;margin:-1px;overflow:hidden;padding:0;position:absolute;width:1px}.ui-helper-reset{margin:0;padding:0;border:0;outline:0;line-height:1.3;text-decoration:none;font-size:100%;list-style:none}.ui-helper-clearfix:after,.ui-helper-clearfix:before{content:"";display:table;border-collapse:collapse}.ui-helper-clearfix:after{clear:both}.ui-helper-zfix{width:100%;height:100%;top:0;left:0;position:absolute;opacity:0;filter:Alpha(Opacity=0)}.ui-front{z-index:100}.ui-state-disabled{cursor:default!important;pointer-events:none}.ui-icon{display:inline-block;vertical-align:middle;margin-top:-.25em;position:relative;text-indent:-99999px;overflow:hidden;background-repeat:no-repeat}.ui-widget-icon-block{left:50%;margin-left:-8px;display:block}.ui-widget-overlay{position:fixed;top:0;left:0;width:100%;height:100%}.ui-accordion .ui-accordion-header{display:block;cursor:pointer;position:relative;margin:2px 0 0;padding:.5em .5em .5em .7em;font-size:100%}.ui-accordion .ui-accordion-content{padding:1em 2.2em;border-top:0;overflow:auto}.ui-autocomplete{position:absolute;top:0;left:0;cursor:default}.ui-menu{list-style:none;padding:0;margin:0;display:block;outline:0}.ui-menu .ui-menu{position:absolute}.ui-menu .ui-menu-item{margin:0;cursor:pointer;list-style-image:url(data:image/gif;base64,R0lGODlhAQABAIAAAAAAAP///yH5BAEAAAAALAAAAAABAAEAAAIBRAA7)}.ui-menu .ui-menu-item-wrapper{position:relative;padding:3px 1em 3px .4em}.ui-menu .ui-menu-divider{margin:5px 0;height:0;font-size:0;line-height:0;border-width:1px 0 0}.ui-menu .ui-state-active,.ui-menu .ui-state-focus{margin:-1px}.ui-menu-icons{position:relative}.ui-menu-icons .ui-menu-item-wrapper{padding-left:2em}.ui-menu .ui-icon{position:absolute;top:0;bottom:0;left:.2em;margin:auto 0}.ui-menu .ui-menu-icon{left:auto;right:0}.ui-button{padding:.4em 1em;display:inline-block;position:relative;line-height:normal;margin-right:.1em;cursor:pointer;vertical-align:middle;text-align:center;-webkit-user-select:none;-moz-user-select:none;-ms-user-select:none;user-select:none;overflow:visible}.ui-button,.ui-button:active,.ui-button:hover,.ui-button:link,.ui-button:visited{text-decoration:none}.ui-button-icon-only{width:2em;box-sizing:border-box;text-indent:-9999px;white-space:nowrap}input.ui-button.ui-button-icon-only{text-indent:0}.ui-button-icon-only .ui-icon{position:absolute;top:50%;left:50%;margin-top:-8px;margin-left:-8px}.ui-button.ui-icon-notext .ui-icon{padding:0;width:2.1em;height:2.1em;text-indent:-9999px;white-space:nowrap}input.ui-button.ui-icon-notext .ui-icon{width:auto;height:auto;text-indent:0;white-space:normal;padding:.4em 1em}button.ui-button::-moz-focus-inner,input.ui-button::-moz-focus-inner{border:0;padding:0}.ui-controlgroup{vertical-align:middle;display:inline-block}.ui-controlgroup>.ui-controlgroup-item{float:left;margin-left:0;margin-right:0}.ui-controlgroup>.ui-controlgroup-item.ui-visual-focus,.ui-controlgroup>.ui-controlgroup-item:focus{z-index:9999}.ui-controlgroup-vertical>.ui-controlgroup-item{display:block;float:none;width:100%;margin-top:0;margin-bottom:0;text-align:left}.ui-controlgroup-vertical .ui-controlgroup-item{box-sizing:border-box}.ui-controlgroup .ui-controlgroup-label{padding:.4em 1em}.ui-controlgroup .ui-controlgroup-label span{font-size:80%}.ui-controlgroup-horizontal .ui-controlgroup-label+.ui-controlgroup-item{border-left:none}.ui-controlgroup-vertical .ui-controlgroup-label+.ui-controlgroup-item{border-top:none}.ui-controlgroup-horizontal .ui-controlgroup-label.ui-widget-content{border-right:none}.ui-controlgroup-vertical .ui-controlgroup-label.ui-widget-content{border-bottom:none}.ui-controlgroup-vertical .ui-spinner-input{width:75%;width:calc(100% - 2.4em)}.ui-controlgroup-vertical .ui-spinner .ui-spinner-up{border-top-style:solid}.ui-checkboxradio-label .ui-icon-background{box-shadow:inset 1px 1px 1px #ccc;border-radius:.12em;border:none}.ui-checkboxradio-radio-label .ui-icon-background{width:16px;height:16px;border-radius:1em;overflow:visible;border:none}.ui-checkboxradio-radio-label.ui-checkboxradio-checked .ui-icon,.ui-checkboxradio-radio-label.ui-checkboxradio-checked:hover .ui-icon{background-image:none;width:8px;height:8px;border-width:4px;border-style:solid}.ui-checkboxradio-disabled{pointer-events:none}.ui-datepicker{width:17em;padding:.2em .2em 0;display:none}.ui-datepicker .ui-datepicker-header{position:relative;padding:.2em 0}.ui-datepicker .ui-datepicker-next,.ui-datepicker .ui-datepicker-prev{position:absolute;top:2px;width:1.8em;height:1.8em}.ui-datepicker .ui-datepicker-next-hover,.ui-datepicker .ui-datepicker-prev-hover{top:1px}.ui-datepicker .ui-datepicker-prev{left:2px}.ui-datepicker .ui-datepicker-next{right:2px}.ui-datepicker .ui-datepicker-prev-hover{left:1px}.ui-datepicker .ui-datepicker-next-hover{right:1px}.ui-datepicker .ui-datepicker-next span,.ui-datepicker .ui-datepicker-prev span{display:block;position:absolute;left:50%;margin-left:-8px;top:50%;margin-top:-8px}.ui-datepicker .ui-datepicker-title{margin:0 2.3em;line-height:1.8em;text-align:center}.ui-datepicker .ui-datepicker-title select{font-size:1em;margin:1px 0}.ui-datepicker select.ui-datepicker-month,.ui-datepicker select.ui-datepicker-year{width:45%}.ui-datepicker table{width:100%;font-size:.9em;border-collapse:collapse;margin:0 0 .4em}.ui-datepicker th{padding:.7em .3em;text-align:center;font-weight:700;border:0}.ui-datepicker td{border:0;padding:1px}.ui-datepicker td a,.ui-datepicker td span{display:block;padding:.2em;text-align:right;text-decoration:none}.ui-datepicker .ui-datepicker-buttonpane{background-image:none;margin:.7em 0 0;padding:0 .2em;border-left:0;border-right:0;border-bottom:0}.ui-datepicker .ui-datepicker-buttonpane button{float:right;margin:.5em .2em .4em;cursor:pointer;padding:.2em .6em .3em;width:auto;overflow:visible}.ui-datepicker .ui-datepicker-buttonpane button.ui-datepicker-current{float:left}.ui-datepicker.ui-datepicker-multi{width:auto}.ui-datepicker-multi .ui-datepicker-group{float:left}.ui-datepicker-multi .ui-datepicker-group table{width:95%;margin:0 auto .4em}.ui-datepicker-multi-2 .ui-datepicker-group{width:50%}.ui-datepicker-multi-3 .ui-datepicker-group{width:33.3%}.ui-datepicker-multi-4 .ui-datepicker-group{width:25%}.ui-datepicker-multi .ui-datepicker-group-last .ui-datepicker-header,.ui-datepicker-multi .ui-datepicker-group-middle .ui-datepicker-header{border-left-width:0}.ui-datepicker-multi .ui-datepicker-buttonpane{clear:left}.ui-datepicker-row-break{clear:both;width:100%;font-size:0}.ui-datepicker-rtl{direction:rtl}.ui-datepicker-rtl .ui-datepicker-prev{right:2px;left:auto}.ui-datepicker-rtl .ui-datepicker-next{left:2px;right:auto}.ui-datepicker-rtl .ui-datepicker-prev:hover{right:1px;left:auto}.ui-datepicker-rtl .ui-datepicker-next:hover{left:1px;right:auto}.ui-datepicker-rtl .ui-datepicker-buttonpane{clear:right}.ui-datepicker-rtl .ui-datepicker-buttonpane button{float:left}.ui-datepicker-rtl .ui-datepicker-buttonpane button.ui-datepicker-current,.ui-datepicker-rtl .ui-datepicker-group{float:right}.ui-datepicker-rtl .ui-datepicker-group-last .ui-datepicker-header,.ui-datepicker-rtl .ui-datepicker-group-middle .ui-datepicker-header{border-right-width:0;border-left-width:1px}.ui-datepicker .ui-icon{display:block;text-indent:-99999px;overflow:hidden;background-repeat:no-repeat;left:.5em;top:.3em}.ui-dialog{position:absolute;top:0;left:0;padding:.2em;outline:0}.ui-dialog .ui-dialog-titlebar{padding:.4em 1em;position:relative}.ui-dialog .ui-dialog-title{float:left;margin:.1em 0;white-space:nowrap;width:90%;overflow:hidden;text-overflow:ellipsis}.ui-dialog .ui-dialog-titlebar-close{position:absolute;right:.3em;top:50%;width:20px;margin:-10px 0 0;padding:1px;height:20px}.ui-dialog .ui-dialog-content{position:relative;border:0;padding:.5em 1em;background:0 0;overflow:auto}.ui-dialog .ui-dialog-buttonpane{text-align:left;border-width:1px 0 0;background-image:none;margin-top:.5em;padding:.3em 1em .5em .4em}.ui-dialog .ui-dialog-buttonpane .ui-dialog-buttonset{float:right}.ui-dialog .ui-dialog-buttonpane button{margin:.5em .4em .5em 0;cursor:pointer}.ui-dialog .ui-resizable-n{height:2px;top:0}.ui-dialog .ui-resizable-e{width:2px;right:0}.ui-dialog .ui-resizable-s{height:2px;bottom:0}.ui-dialog .ui-resizable-w{width:2px;left:0}.ui-dialog .ui-resizable-ne,.ui-dialog .ui-resizable-nw,.ui-dialog .ui-resizable-se,.ui-dialog .ui-resizable-sw{width:7px;height:7px}.ui-dialog .ui-resizable-se{right:0;bottom:0}.ui-dialog .ui-resizable-sw{left:0;bottom:0}.ui-dialog .ui-resizable-ne{right:0;top:0}.ui-dialog .ui-resizable-nw{left:0;top:0}.ui-draggable .ui-dialog-titlebar{cursor:move}.ui-draggable-handle{-ms-touch-action:none;touch-action:none}.ui-resizable{position:relative}.ui-resizable-handle{position:absolute;font-size:.1px;display:block;-ms-touch-action:none;touch-action:none}.ui-resizable-autohide .ui-resizable-handle,.ui-resizable-disabled .ui-resizable-handle{display:none}.ui-resizable-n{cursor:n-resize;height:7px;width:100%;top:-5px;left:0}.ui-resizable-s{cursor:s-resize;height:7px;width:100%;bottom:-5px;left:0}.ui-resizable-e{cursor:e-resize;width:7px;right:-5px;top:0;height:100%}.ui-resizable-w{cursor:w-resize;width:7px;left:-5px;top:0;height:100%}.ui-resizable-se{cursor:se-resize;width:12px;height:12px;right:1px;bottom:1px}.ui-resizable-sw{cursor:sw-resize;width:9px;height:9px;left:-5px;bottom:-5px}.ui-resizable-nw{cursor:nw-resize;width:9px;height:9px;left:-5px;top:-5px}.ui-resizable-ne{cursor:ne-resize;width:9px;height:9px;right:-5px;top:-5px}.ui-progressbar{height:2em;text-align:left;overflow:hidden}.ui-progressbar .ui-progressbar-value{margin:-1px;height:100%}.ui-progressbar .ui-progressbar-overlay{background:url(data:image/gif;base64,R0lGODlhKAAoAIABAAAAAP///yH/C05FVFNDQVBFMi4wAwEAAAAh+QQJAQABACwAAAAAKAAoAAACkYwNqXrdC52DS06a7MFZI+4FHBCKoDeWKXqymPqGqxvJrXZbMx7Ttc+w9XgU2FB3lOyQRWET2IFGiU9m1frDVpxZZc6bfHwv4c1YXP6k1Vdy292Fb6UkuvFtXpvWSzA+HycXJHUXiGYIiMg2R6W459gnWGfHNdjIqDWVqemH2ekpObkpOlppWUqZiqr6edqqWQAAIfkECQEAAQAsAAAAACgAKAAAApSMgZnGfaqcg1E2uuzDmmHUBR8Qil95hiPKqWn3aqtLsS18y7G1SzNeowWBENtQd+T1JktP05nzPTdJZlR6vUxNWWjV+vUWhWNkWFwxl9VpZRedYcflIOLafaa28XdsH/ynlcc1uPVDZxQIR0K25+cICCmoqCe5mGhZOfeYSUh5yJcJyrkZWWpaR8doJ2o4NYq62lAAACH5BAkBAAEALAAAAAAoACgAAAKVDI4Yy22ZnINRNqosw0Bv7i1gyHUkFj7oSaWlu3ovC8GxNso5fluz3qLVhBVeT/Lz7ZTHyxL5dDalQWPVOsQWtRnuwXaFTj9jVVh8pma9JjZ4zYSj5ZOyma7uuolffh+IR5aW97cHuBUXKGKXlKjn+DiHWMcYJah4N0lYCMlJOXipGRr5qdgoSTrqWSq6WFl2ypoaUAAAIfkECQEAAQAsAAAAACgAKAAAApaEb6HLgd/iO7FNWtcFWe+ufODGjRfoiJ2akShbueb0wtI50zm02pbvwfWEMWBQ1zKGlLIhskiEPm9R6vRXxV4ZzWT2yHOGpWMyorblKlNp8HmHEb/lCXjcW7bmtXP8Xt229OVWR1fod2eWqNfHuMjXCPkIGNileOiImVmCOEmoSfn3yXlJWmoHGhqp6ilYuWYpmTqKUgAAIfkECQEAAQAsAAAAACgAKAAAApiEH6kb58biQ3FNWtMFWW3eNVcojuFGfqnZqSebuS06w5V80/X02pKe8zFwP6EFWOT1lDFk8rGERh1TTNOocQ61Hm4Xm2VexUHpzjymViHrFbiELsefVrn6XKfnt2Q9G/+Xdie499XHd2g4h7ioOGhXGJboGAnXSBnoBwKYyfioubZJ2Hn0RuRZaflZOil56Zp6iioKSXpUAAAh+QQJAQABACwAAAAAKAAoAAACkoQRqRvnxuI7kU1a1UU5bd5tnSeOZXhmn5lWK3qNTWvRdQxP8qvaC+/yaYQzXO7BMvaUEmJRd3TsiMAgswmNYrSgZdYrTX6tSHGZO73ezuAw2uxuQ+BbeZfMxsexY35+/Qe4J1inV0g4x3WHuMhIl2jXOKT2Q+VU5fgoSUI52VfZyfkJGkha6jmY+aaYdirq+lQAACH5BAkBAAEALAAAAAAoACgAAAKWBIKpYe0L3YNKToqswUlvznigd4wiR4KhZrKt9Upqip61i9E3vMvxRdHlbEFiEXfk9YARYxOZZD6VQ2pUunBmtRXo1Lf8hMVVcNl8JafV38aM2/Fu5V16Bn63r6xt97j09+MXSFi4BniGFae3hzbH9+hYBzkpuUh5aZmHuanZOZgIuvbGiNeomCnaxxap2upaCZsq+1kAACH5BAkBAAEALAAAAAAoACgAAAKXjI8By5zf4kOxTVrXNVlv1X0d8IGZGKLnNpYtm8Lr9cqVeuOSvfOW79D9aDHizNhDJidFZhNydEahOaDH6nomtJjp1tutKoNWkvA6JqfRVLHU/QUfau9l2x7G54d1fl995xcIGAdXqMfBNadoYrhH+Mg2KBlpVpbluCiXmMnZ2Sh4GBqJ+ckIOqqJ6LmKSllZmsoq6wpQAAAh+QQJAQABACwAAAAAKAAoAAAClYx/oLvoxuJDkU1a1YUZbJ59nSd2ZXhWqbRa2/gF8Gu2DY3iqs7yrq+xBYEkYvFSM8aSSObE+ZgRl1BHFZNr7pRCavZ5BW2142hY3AN/zWtsmf12p9XxxFl2lpLn1rseztfXZjdIWIf2s5dItwjYKBgo9yg5pHgzJXTEeGlZuenpyPmpGQoKOWkYmSpaSnqKileI2FAAACH5BAkBAAEALAAAAAAoACgAAAKVjB+gu+jG4kORTVrVhRlsnn2dJ3ZleFaptFrb+CXmO9OozeL5VfP99HvAWhpiUdcwkpBH3825AwYdU8xTqlLGhtCosArKMpvfa1mMRae9VvWZfeB2XfPkeLmm18lUcBj+p5dnN8jXZ3YIGEhYuOUn45aoCDkp16hl5IjYJvjWKcnoGQpqyPlpOhr3aElaqrq56Bq7VAAAOw==);height:100%;filter:alpha(opacity=25);opacity:.25}.ui-progressbar-indeterminate .ui-progressbar-value{background-image:none}.ui-selectable{-ms-touch-action:none;touch-action:none}.ui-selectable-helper{position:absolute;z-index:100;border:1px dotted #000}.ui-selectmenu-menu{padding:0;margin:0;position:absolute;top:0;left:0;display:none}.ui-selectmenu-menu .ui-menu{overflow:auto;overflow-x:hidden;padding-bottom:1px}.ui-selectmenu-menu .ui-menu .ui-selectmenu-optgroup{font-size:1em;font-weight:700;line-height:1.5;padding:2px .4em;margin:.5em 0 0;height:auto;border:0}.ui-selectmenu-open{display:block}.ui-selectmenu-text{display:block;margin-right:20px;overflow:hidden;text-overflow:ellipsis}.ui-selectmenu-button.ui-button{text-align:left;white-space:nowrap;width:14em}.ui-selectmenu-icon.ui-icon{float:right;margin-top:0}.ui-slider{position:relative;text-align:left}.ui-slider .ui-slider-handle{position:absolute;z-index:2;width:1.2em;height:1.2em;cursor:default;-ms-touch-action:none;touch-action:none}.ui-slider .ui-slider-range{position:absolute;z-index:1;font-size:.7em;display:block;border:0;background-position:0 0}.ui-slider.ui-state-disabled .ui-slider-handle,.ui-slider.ui-state-disabled .ui-slider-range{filter:inherit}.ui-slider-horizontal{height:.8em}.ui-slider-horizontal .ui-slider-handle{top:-.3em;margin-left:-.6em}.ui-slider-horizontal .ui-slider-range{top:0;height:100%}.ui-slider-horizontal .ui-slider-range-min{left:0}.ui-slider-horizontal .ui-slider-range-max{right:0}.ui-slider-vertical{width:.8em;height:100px}.ui-slider-vertical .ui-slider-handle{left:-.3em;margin-left:0;margin-bottom:-.6em}.ui-slider-vertical .ui-slider-range{left:0;width:100%}.ui-slider-vertical .ui-slider-range-min{bottom:0}.ui-slider-vertical .ui-slider-range-max{top:0}.ui-sortable-handle{-ms-touch-action:none;touch-action:none}.ui-spinner{position:relative;display:inline-block;overflow:hidden;padding:0;vertical-align:middle}.ui-spinner-input{border:none;background:0 0;color:inherit;padding:.222em 0;margin:.2em 2em .2em .4em;vertical-align:middle}.ui-spinner-button{width:1.6em;height:50%;font-size:.5em;padding:0;margin:0;text-align:center;position:absolute;cursor:default;display:block;overflow:hidden;right:0}.ui-spinner a.ui-spinner-button{border-top-style:none;border-bottom-style:none;border-right-style:none}.ui-spinner-up{top:0}.ui-spinner-down{bottom:0}.ui-tabs{position:relative;padding:.2em}.ui-tabs .ui-tabs-nav{margin:0;padding:.2em .2em 0}.ui-tabs .ui-tabs-nav li{list-style:none;float:left;position:relative;top:0;margin:1px .2em 0 0;border-bottom-width:0;padding:0;white-space:nowrap}.ui-tabs .ui-tabs-nav .ui-tabs-anchor{float:left;padding:.5em 1em;text-decoration:none}.ui-tabs .ui-tabs-nav li.ui-tabs-active{margin-bottom:-1px;padding-bottom:1px}.ui-tabs .ui-tabs-nav li.ui-state-disabled .ui-tabs-anchor,.ui-tabs .ui-tabs-nav li.ui-tabs-active .ui-tabs-anchor,.ui-tabs .ui-tabs-nav li.ui-tabs-loading .ui-tabs-anchor{cursor:text}.ui-tabs-collapsible .ui-tabs-nav li.ui-tabs-active .ui-tabs-anchor{cursor:pointer}.ui-tabs .ui-tabs-panel{display:block;border-width:0;padding:1em 1.4em;background:0 0}.ui-tooltip{padding:8px;position:absolute;z-index:9999;max-width:300px}body .ui-tooltip{border-width:2px}.ui-widget{font-family:Verdana,Arial,sans-serif;font-size:1.1em}.ui-widget .ui-widget{font-size:1em}.ui-widget button,.ui-widget input,.ui-widget select,.ui-widget textarea{font-family:Verdana,Arial,sans-serif;font-size:1em}.ui-widget.ui-widget-content{border:1px solid #d3d3d3}.ui-widget-content{border:1px solid #aaa;background:#fff;color:#222}.ui-widget-content a{color:#222}.ui-widget-header{border:1px solid #aaa;background:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAAEAAABkEAAAAAAy19n/AAAABGdBTUEAALGPC/xhBQAAACBjSFJNAAB6JgAAgIQAAPoAAACA6AAAdTAAAOpgAAA6mAAAF3CculE8AAAAAmJLR0T//xSrMc0AAAAHdElNRQfgCQ4NIgiW7vkhAAAATUlEQVQY073OoQ2AQBAF0Z/p4qrZbuiMam414iQUQLKg+Sgc+pInR4yODWmKof1EgQM3XLjwhbvGjTtOnLjzrLhw4vrKwA0typx1++MFHrwm/bbhD4gAAAAldEVYdGRhdGU6Y3JlYXRlADIwMTYtMDktMTRUMTM6MzQ6MDgtMDQ6MDBfRG64AAAAJXRFWHRkYXRlOm1vZGlmeQAyMDE2LTA5LTE0VDEzOjM0OjA4LTA0OjAwLhnWBAAAAABJRU5ErkJggg==) 50% 50% repeat-x #ccc;color:#222;font-weight:700}.ui-widget-header a{color:#222}.ui-button,.ui-state-default,.ui-widget-content .ui-state-default,.ui-widget-header .ui-state-default,html .ui-button.ui-state-disabled:active,html .ui-button.ui-state-disabled:hover{border:1px solid #d3d3d3;background:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAAEAAAGQEAAAAAAao4lEAAAABGdBTUEAALGPC/xhBQAAACBjSFJNAAB6JgAAgIQAAPoAAACA6AAAdTAAAOpgAAA6mAAAF3CculE8AAAAAmJLR0T//xSrMc0AAAAHdElNRQfgCQ4NIgiW7vkhAAAATElEQVQ4y2N4l8fEwDCKRhF1EcOzZwzPjRie32Fi3MvEeIGJ8SsT4zcmRg4mRk4mxm9MjF+ZGB8zfGRmYljF8EmOiUF4wB08ioYEAgDUMBI63vAgyAAAACV0RVh0ZGF0ZTpjcmVhdGUAMjAxNi0wOS0xNFQxMzozNDowOC0wNDowMF9EbrgAAAAldEVYdGRhdGU6bW9kaWZ5ADIwMTYtMDktMTRUMTM6MzQ6MDgtMDQ6MDAuGdYEAAAAAElFTkSuQmCC) 50% 50% repeat-x #e6e6e6;font-weight:400;color:#555}.ui-button,.ui-state-default a,.ui-state-default a:link,.ui-state-default a:visited,a.ui-button,a:link.ui-button,a:visited.ui-button{color:#555;text-decoration:none}.ui-button:focus,.ui-button:hover,.ui-state-focus,.ui-state-hover,.ui-widget-content .ui-state-focus,.ui-widget-content .ui-state-hover,.ui-widget-header .ui-state-focus,.ui-widget-header .ui-state-hover{border:1px solid #999;background:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAAEAAAGQEAAAAAAao4lEAAAABGdBTUEAALGPC/xhBQAAACBjSFJNAAB6JgAAgIQAAPoAAACA6AAAdTAAAOpgAAA6mAAAF3CculE8AAAAAmJLR0T//xSrMc0AAAAHdElNRQfgCQ4NIgiW7vkhAAAAS0lEQVQ4y2N4+p+JgWEUjSIqo6+3GW57MTH+YWIUZ2I0Ybj/h4kph+HRByamdoanjxme+zExBjAxmjAx/mZiXMHEIDPwDh5FQwEBABzuEyBfPm9/AAAAJXRFWHRkYXRlOmNyZWF0ZQAyMDE2LTA5LTE0VDEzOjM0OjA4LTA0OjAwX0RuuAAAACV0RVh0ZGF0ZTptb2RpZnkAMjAxNi0wOS0xNFQxMzozNDowOC0wNDowMC4Z1gQAAAAASUVORK5CYII=) 50% 50% repeat-x #dadada;font-weight:400;color:#212121}.ui-state-focus a,.ui-state-focus a:hover,.ui-state-focus a:link,.ui-state-focus a:visited,.ui-state-hover a,.ui-state-hover a:hover,.ui-state-hover a:link,.ui-state-hover a:visited,a.ui-button:focus,a.ui-button:hover{color:#212121;text-decoration:none}.ui-visual-focus{box-shadow:0 0 3px 1px #5e9ed6}.ui-button.ui-state-active:hover,.ui-button:active,.ui-state-active,.ui-widget-content .ui-state-active,.ui-widget-header .ui-state-active,a.ui-button:active{border:1px solid #aaa;background:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAAEAAAGQAQAAAABHIzd2AAAABGdBTUEAALGPC/xhBQAAACBjSFJNAAB6JgAAgIQAAPoAAACA6AAAdTAAAOpgAAA6mAAAF3CculE8AAAAAmJLR0QAAd2KE6QAAAAHdElNRQfgCQ4NIgiW7vkhAAAAEUlEQVQoz2NoYBiFo3AU4oAAlWjIAdM0sWkAAAAldEVYdGRhdGU6Y3JlYXRlADIwMTYtMDktMTRUMTM6MzQ6MDgtMDQ6MDBfRG64AAAAJXRFWHRkYXRlOm1vZGlmeQAyMDE2LTA5LTE0VDEzOjM0OjA4LTA0OjAwLhnWBAAAAABJRU5ErkJggg==) 50% 50% repeat-x #fff;font-weight:400;color:#212121}.ui-icon-background,.ui-state-active .ui-icon-background{border:#aaa;background-color:#212121}.ui-state-active a,.ui-state-active a:link,.ui-state-active a:visited{color:#212121;text-decoration:none}.ui-state-highlight,.ui-widget-content .ui-state-highlight,.ui-widget-header .ui-state-highlight{border:1px solid #fcefa1;background:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAAEAAAGQEAIAAACwqkHPAAAABGdBTUEAALGPC/xhBQAAACBjSFJNAAB6JgAAgIQAAPoAAACA6AAAdTAAAOpgAAA6mAAAF3CculE8AAAABmJLR0T///////8JWPfcAAAAB3RJTUUH4AkODSIIlu75IQAAAI1JREFUSMftzyEKAkEUgOF/nmIQbIOIsKMGQRgxewjrVqtZMGnd+3gDwYN4hRV2i+MbweIVRMNLX/jTT77ppjkLABiGYRjfBtWU6prcffbuXvAESmHIjK0wYu52QkHkJBQs3VGYsKIiXzQ08dPIDz20U3FjFux5Rb22SfAEVwoDPGtB6ND/i2nDMIwf8gY8YSRTiOx5LgAAACV0RVh0ZGF0ZTpjcmVhdGUAMjAxNi0wOS0xNFQxMzozNDowOC0wNDowMF9EbrgAAAAldEVYdGRhdGU6bW9kaWZ5ADIwMTYtMDktMTRUMTM6MzQ6MDgtMDQ6MDAuGdYEAAAAAElFTkSuQmCC) 50% 50% repeat-x #fbf9ee;color:#363636}.ui-state-checked{border:1px solid #fcefa1;background:#fbf9ee}.ui-state-highlight a,.ui-widget-content .ui-state-highlight a,.ui-widget-header .ui-state-highlight a{color:#363636}.ui-state-error,.ui-widget-content .ui-state-error,.ui-widget-header .ui-state-error{border:1px solid #cd0a0a;background:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAAEAAAGQEAIAAACwqkHPAAAABGdBTUEAALGPC/xhBQAAACBjSFJNAAB6JgAAgIQAAPoAAACA6AAAdTAAAOpgAAA6mAAAF3CculE8AAAABmJLR0T///////8JWPfcAAAAB3RJTUUH4AkODSIIlu75IQAAAIpJREFUSMftz7ENAWEYh/Hn/xYS51whVhCN1g5KI1jAAJbQ0ItEfRMYgA0uZvg+yR2J7j4FsYFQvNWveKqHtHjM7hMDAMdxHOfb0LZ1HQLJmnGckrJmFyvS8Da6ro0eW52NXKXCh4KjktHXm1ejVDRy7bkYmTY6GV1WOhgd5iwNKBj8xbTjOM4PeQJHLShkmp8JSAAAACV0RVh0ZGF0ZTpjcmVhdGUAMjAxNi0wOS0xNFQxMzozNDowOC0wNDowMF9EbrgAAAAldEVYdGRhdGU6bW9kaWZ5ADIwMTYtMDktMTRUMTM6MzQ6MDgtMDQ6MDAuGdYEAAAAAElFTkSuQmCC) 50% 50% repeat-x #fef1ec;color:#cd0a0a}.ui-state-error a,.ui-state-error-text,.ui-widget-content .ui-state-error a,.ui-widget-content .ui-state-error-text,.ui-widget-header .ui-state-error a,.ui-widget-header .ui-state-error-text{color:#cd0a0a}.ui-priority-primary,.ui-widget-content .ui-priority-primary,.ui-widget-header .ui-priority-primary{font-weight:700}.ui-priority-secondary,.ui-widget-content .ui-priority-secondary,.ui-widget-header .ui-priority-secondary{opacity:.7;filter:Alpha(Opacity=70);font-weight:400}.ui-state-disabled,.ui-widget-content .ui-state-disabled,.ui-widget-header .ui-state-disabled{opacity:.35;filter:Alpha(Opacity=35);background-image:none}.ui-state-disabled .ui-icon{filter:Alpha(Opacity=35)}.ui-icon{width:16px;height:16px}.ui-icon,.ui-widget-content .ui-icon,.ui-widget-header .ui-icon{background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAQAAAADwCAQAAABFnnJAAAAABGdBTUEAALGPC/xhBQAAACBjSFJNAAB6JgAAgIQAAPoAAACA6AAAdTAAAOpgAAA6mAAAF3CculE8AAAAAmJLR0QAIn/tYtYAAAAHdElNRQffBgEKJRWQ+SdFAAAaVElEQVR42u2dbZAlVXnHfw0kFCEsaAggLLsllQgmhsruQKV8SZWURe6Yqk3UcsndsYJEyQ7RCMYyO+Nmhg8MwtyJQV4kNbsFxqJqXrJLlEBVuKMCFsYtEHdXo4SYRGAW4q58iHH9kCKWdD706+nz2t33zr0zff5Tu/fefs45ffo8/z6n+zzPeU5wCR5NximDroDHYOEJ0HB4AohoE9IedCXWEp4AebRZApaaRIFeE2Dw90+bsHLOJWAXOgokJQ/+GnsIkQDmDjBM/0yw3T/6/GF89rY2je3ciRKrXUGk/uWYAqaSN1AfkSdALzrAXTVKSPIm92F51MkLAQHLwDIBgaHkOtc4dAjSeYDkEpP7QIcQpObJIyonqJQ/uct057edO6xZd9eSbde4jpD1AOYO0BWme9A+fERnN6nQXEq9e9M0BOVLrtfPDBmC0jOB5rvIdA9mjVr13rGXYL43zXU394FZybZ+Zl2hPAHMCAfeNG2WKhPMPAQlJQ/+GnuIXhNgvaPN0kZSrx2eAA2HnwlsODwBGg5PgIbDE6Dh8ARoODwBGg5PgIbD+wMU8w66/muMMv4Abh4BNmNM2+gPYD6DXT11/AHs5vCo7huKJOX8AdwsYOYm1Ctol+a7a9k29dtKXyp86kvfMN4Asj9ABP1seJLKZG/Ty225XfwBTLUzn92e34wwLjv53BAQ/QFU30UsO/UC6jT2+9PFH8B0/7nVTU+f0OptUOZM6wJVjEEmg+uw+wOYyGXrf5Ir9+ZgAwbfOHX9AQZd/zWGNwc3HH4iqOHwBGg4PAEaDk+AhsMToOHwBGg4PAEajtMGXYGhQzjAWf76c6Wl639avex9aYRB1iC01qC6KciecwBXLg4BIRht/S7xAcIKkrKoeg5b/SPVB8ZS7OSomtvtClxSlch7ipDAdvmBwwXo8wcODeRyCaHB2ONSv8AgEz/LnSOR2FvAfIVmAoWW3GC7iYX654cA18vXeevYGynoQQcfGi2RtlG0Tg3CNHeglObPrjpLcnvp6xAa5Oays6sz3wb5WgZQ9iEwdLh7bKlc2FntHndTbuBQuklBLuVWbQHTLehStr0NJHmZ18Csi3NJpZaZu0A7g81l2LpYty7adgfZzu7yEFkVdorb5UINyvQAbl1nvafcwLGX6VcdA2MH61Zu4JCmKszDtHkAVOY9TZNocBh0Ddbz+Svk9TOBDYcnQMPhCdBweAI0HJ4ADYcnQMPhCdBwiItDk2Cpg4M9Hng/4dICLhbRavlsa6Ndz1IKGQGShVEu4d6rNUDvUK0sW83dWsAUajazxrVL547slMmf/hralVsgLNQSUC8ONS/hdLFotxXHekcBXVluoSH09XdrAd052oXlte1SubMrsPVA9ZamSwt0xaVhLuHUbUuwdQtE3Txp7DXQlWMP4W6vuVtAerXFQFZtUJDbFpZnylGtTwyFks0GY53BOpDTlCWAewMEJfK61cDchC7nt6/t15/flttGAHsbmBVoJ4CZQBoClHsLyBqgiskiyJWhLj0UPk3nr4Ks3lWfIUxn3xVLkxFcHUHAdP4kp/oZwFZyFrvBtL65WMuS/gCmBhAfYEyXb66c6RJNZeQvze72pVKBnYCmK1guBJBYLl2CG0zqXU63vXGrJWWHADd3qtAaIsI8CtbJ7da86utwG4Pru7SZyqm+qY39GUAJHx8gj7Z1x6QNB0+AhsNPBTccngANhydAw+EJ0HB4AjQcngC9xiDN2RVQ9AewwWSvcrn0dk17d79Rv3aBZbJ7yK5d9gcwwWQxd5klTCx2uxwWmOpRd3GVeXl4YF3+alewLr+p9AEhmwjKV8se7VeebMwvjay2+7frRDOYLHa23IE2Xf6oztppWjwaOkndr3RNoH4G0DkdmO1V2dBQxWkhunPsblP6GAYhrra+oMRR1XlV57evbB5KFPcLyJqw7A7cxSEkKJE3kbotgbYv3q4eQsKkRlsP4V6yKUbAGiPrAfKGwipVs+0kYDe21h0dg1wPou4hxE9Vit7cxaoziL3HkKhfHAKW00qpOvCog4/cvdRYNvoDuFj77eEhzMh8AdQuFeamzwYhfXSRJGVQUppPUdWhpi9QWwNDbQfuYizVPQT2wtjq5rVY9UHT5SESsBB0aJTrAm8OFjE0XfNawc8EimiY+j0BGg9PgIbDE6Dh8ARoODwBGo7hI0BruKxlGx1FArjZsk0mm9BJqkvRorsmr2KDjoMwNCgXLt4lnHTAaI36dElI0jKmqxqyPsMG2gG8DkQCmGepzbPdyV3doqukQJhOlKrX7kVd/2iaoqvJn3yrFlQ93/u4bTW/wZERQAz3LiOzh+tCpgcEsfpXlOcyd+1R17/CqGHtbHJ29flFj4JiKW7hIxqHxBbgtrrdhMTXRqf+oi9OsRex/TYdlSXFdMXwEaZdzhuFvEtYgKymIvSuDG4OEXqnsiKBdC4Z6hrawieIBN9gW8DXQRYtPN9k+gAj9l0vXLeV0MkjCoTSc0RiCFZH5Rfr06uw8g1AmbeArIl1Pnm2LZlM8tFU2gUCaSAJcmdXPQOY/YnE8BEeKcT9Amyeaia3y7o7WaykZbu8RgaOxxIs45/6lRg2hxD9Q6RHXzBsO4f67nmNMXy2AI81hSdAw+EJ0HB4AjQcG4kAU+lMw1Rfyr+E7fHfkL061UFEgPm44VaZr1zSYxZLvw0hzwjeAmWVOMVM+n1GmXuqFj0u4Xmu5jCHuZrnlRSYstZ+dyzdrTmHXm7LCfcV/sxnSLUUzQOEPMJzwNmM5xJnr2Tz6fF93KApOpskOshOw8oiufQICzyXUyEs8gGhcWcK6ae5tYRcrKGqdrvZJ/weZ7/weztXM8sIcJhJvsIRbQuoz+FibtPv/GnbFDtKkbW87RrTKb+EAHMAPC4kX8kVLhPkGFs1zXsQlBQIGUm/H1Zc4re4IvdbJEBkCRhLZcUlYiHTAgWmmdGu39UZs0aE38UabucwI2wG3sKnGdEQ4DgAb6i4wigkmdIOnCX5FGYCFCkeQDYRlKi+W0wQ4zngKD/mS4bqb48/d2pTbDLkXuQ5gQBF7BNMyfuEvgrgVkgpMM2thR4ha0B9Q27iifT7Vco6bOZ8As401PLPDTJzD5jI1RtQB4pSylEsUf9n+GT+cDYT2LUUcJQfS2nEKpwb2/JChT9PhF8xlD/Gt4znf5LMZLyPJyUCZBSQO/8IrcKnXLv3G2s6yT9yN3Ajk8r8J4AXct9lTDOT/ltbJOq/nzNECrhOBavUX8TrATiF17QpzgHQPKDYeoCEArCPJ7VpAtA+5F1Z+CxiE5+Pv31IIb2IDjALTNJhhzQEFC2pVZeZ2qMk2FJ8geukY5H6D3IG8FGAeNAvYQuQ1V+8wHOsZfxS+m1Ektl6ALgkVvyTXMLzCvkUzzMPPMmUpg8w45e5Mf1WRJutPMxuJoFTCZnkTINDyTS3KpW0NfdPh+3YYEvxQQUBxtkH7ORg/Bw1x0QkqG4Mkvl9pjXP3fHniEJm6wEipUcUUL2GTQlyVS+wufCpaiKYJLrPxSFmK7OQey+Y1QwDEWZqdPGHa6ZQ+3Tsh5gCkFO/iQDTue9ypyOr/3E+I/ySYe4SzT3AtOI1r4wckiEq+yw20X4g5BeYkV4BI0oUj3QKV2d7yIPrc/9kLKZvObBYMYUeCQUE9Q+TP8AU8Obc7+cqdeN1EYJC/b0sPcJgzN672Seqf5gI4DEQbCRbgEcFeAI0HJ4ADYcnQMPhCbCx8ETOnuEEkQAth4XZerjsvOmGKaVFfTpny5bf8ucJhb+iZ8OBgvyA4rx5a/nuPsgBvmZpn05hfqEM3hn/mbHAAgvJj/xrYIsu08CMwjd/lffGM1CP8RXeyLjSnPsCO4GDvJErCsZacH/3TWz7YvppbomPRqXdrLD3HUx/7ZTyu9rjoxm+2b7IkzQBsCCYuwE67GGULjBKt/i+TosucJBrOMBOUK6feInNwMtcbGjdhXgyaZHHuT9PgEj9kTVNpkDILks0cNtcYbSe8Iu8jy/yPh5hh6aBpriVecYlm1625ap681WX7dv/i4v4EefzMps1i08n6RASMMGsVg4Y5E9zkk38jlKeNP8iMFayBRPpwdTcnpcfkIzwB7lGcf55xlnkAbqJv0XeHJxMp84wXSlQS35Jl9pyeAsvsspRjnOYHypTTDHDZm7g5T7MA77AhfyA8/gBF/GiNlU0lz5plCPa1AWc5IjWXJPcfWNK6ajQaroFcmpvi191OALwbuAsrgWgxUpGgGeE2fQZpnlGazbVYQVbMOebeYQdfJnf42u8U+FcNsUM+xjvi/rhjfwrv8F/8Ov8C9cpTCofAxJnqQlF/kQOGOSb2K5xfFkQFF+cy++wJy0/WiI7pzyLGlfxz7w99/sbCpeWDwNbgB3k/K0SAlxJ4kwRfd7aFxXcwov8N09xnKdYlaSJ+qeN5w4N9vDRNDyNqgd6ljfzPX6N7/Gb2UNQijZ3k9j7JxTGn0x+Kj83yLNnABHZ2Bvh6yXbbrRwTcUe4h1Cq7xDe/7CDZp/CEzuXrVP2gi7uYEPx+4cMjtDIa88wspum4EkN6m/GAJCNUYmBFhRyj/Mp5jkDj7B7fwtnxXkYxIlRJNQXXmm/uKjX4ZWYQhYMch10peJzN1F+QJj8dhf8OV0J4BblP4WyVBQPsQMYLj7k7eABKq3gNE0QpGaICLk95RP8jfG2tWRB4RG9dsfozMKqN4A7uDjPMg1wAHez518QpAuMMYj/JSxYt5ikKjsXb4sDhIS0qVLGHsG6y9RV7qp85/h5tyvm6X+ZJyo4+/G1zCukJt+wy6t+urLF63qj5y0oo59lNRlS8AKo6BZQP8zPh8/91/D5/mZIsUOxlgs5nU1B0/UmJ7wKIMOlHj4c0c0REkU9P4ADYe3BTQcngANhydAw+EJ0HA0jwCR2Vj1TtNJTbkfcyjnLOXRodse3oY8ASbSBqj+GlI9PkBdtAjT5VpHtF4NX43f//dIFPhr9rCf/XyEj3A3H5dyRq3zcPzrLOCs+C/CXj5HyC3cQsjn2CvlN4evKHozFP0ZZLkthRzpQZTHyF4DJ5jlGI8C13F6avaUC7Htsg398npfYIxJOkwwq5hUic58lO0cYZumFsmE7PXchzxT+Nb0+0meVcyFHuWbjDNJJy5HnA63m8OT2fuu0pBsnntVhc/sFlIEqaPMjCLkZ8hoLkdqzs7MwbPxLPERTudVad3LMGAMmOVyxoAxiQBH2QZsS9V/VFHC+fGnennq8/wiPwHO5v+U8m9yA+O8PrXpl+8nr4znL0NUs55TzKSrClW30AoP57wo5B4uouDlue8y/pifA/BSciA/BDwKHGEbR/lC6Utz31LGlFvZSaWI7Gxjue95bI9Vnqhftsm3eJexDv/LTwD4Ce9RSA8xTgi0Y/XL07ojuT81ZjTfo/rPADNsZ4QRpUdBix3APJFhV4Y53HdAl0k2s5WLuTjzGRLXBkbq366MFBQWvlUz9piqaEMnvvthUdk/bc/d/Sr1dwWfh+Jc+7OczAXCOSTlfzsdYA9b0Nn0NnGy9DVluCj9fBj4A0WKvwQiG8Y4kd1PREhGK/n2mQJ+CPycU9nMbTwWHc7vF/Aqp8dNt8qWCi5fGFO4OTyZzpC30queUb4Td38g+8WJ6lcpcII/yv26l/sNZ1cRLAqNEQ0eJ5UhcEaFUbs4xl8vHA+5X3oGyBuLj/Kp0s8AeyH2wljIWjcbAiY5nVf5JvOsskXRxWaB1tUh1/NHVSmCwp9ZqjrDbKy87HseifqjgWBzNsoBmcPbHKMEyvu3w4Nsi/9k9cMsR3kEeIzoSUPGCl/ma5zF6Up3rGlLgI1zOIf7OIfXxf+bsU1xLHkGuBz1DbWVU9nKVrYCe5MUeWNQxvFJ7SPgsL8FvMzFsW+syt5vc7I6wn8CFyr8aaJAWhOEzPE4XeRewLxljXh0N/sLKeYl87QYjy1ULCm/T9kDXE4UokvuAbIQUePs5bZ8lDB3DJIAZrToph3/S2wuWM3Vz93q2qvrHz1fvMofshI7Zmzip4W8y/w7z7GsbaWQIF0vsE+KQvb7zMQuedP8U6GPmVf4L4gUKaaQA/op4xd4c3AeO/gr4NM8opQucBb3xrRqcYi3SRTLQ0WAvFucnY5rAk+AhqN5tgAPAZ4ADYcnQMNRJMC8Nl74PXw7naT9NvcMuuIevYH4EPhvXAp8n8ukdF+S5scf4r2DrrxHfeR7gLu4FIBLuauQ6p5U/dkM3XuUvcBxwjhitgr/E/cgdkvj8Nkio2tL/o7XL244kCdACxhlFNnU+DZlXtXRC+J/apwdf+6x1KqjcNiAhbjxF7T5bCls8pDjqbuGrOI3aL6va2RDwF3cSLY07G5uEhpGk1s6Yp8JbMVbw+qRrJMVJ24XhCiZqtl8W4oFxriLB7iWmzQluAV0t13hukJGgGj8HyVaYCU+B4gXbmqGA+zUhCaIEKn/mCJccidWt1r9duVEKRZ5gGsZQ62+u2JXrzu5SVvCibQHawQBkiGgE4//3dhmdWnFUfgFspj5KnSBVxTxc5JOX6d+VzzACg8YpOJnBhcXlingBCc4AX3almoASHqAvBlENom49wA2RGt4i4sbM7Xr1T/4HuB47unmxEZ5Coh6gOxub+UeALOjTyvzqo52LM/4gWJjeJiI/XNMd/+i5rt4dIxuGoVHlt/EnWznTm4yxNq+wEmiT7XOkGwapZHGn3fwFwrpZwtr0LOS9D2D3pxs7/ztQRZsKWzykBPcG1vpjmvu8ao7gQwpIgIcVzI6380t0S5Il9mlyNNhj3H8NvkT2PIOBzYkAVwwy++mb/6H+Lpxx4yNjMYSwGNDwlsDGw5PgIbDE6Dh8ARoODwBGg5PgCI6RptAx2oxWGfIEyBk1WIC6t2WEIPCMzxjlHeMvgodqyfDuoPYA2xhj5UEamTkaWlL6LAaWxo6rEoUEul3QCE/IJSkoqB+aXmS7wquMFyfu/pdvJrWBYqxgiMcY1k5JauPJhwK+UKKc/pR4wVAhzZbonMbSjjATkke+Rno8otXoN+tQycVg1HbpRtkRlBNAFDvOGEjACTOHqJRKPu1GisPSwk6Aujzi2X0QsV6aahYfLlOoX4IPMacwatHj2PMpeqfyzVQwFx8dCtzHHMoQQdb/rXBhlB9BJkAkQrK2+SSfC1WmZP23JggYI5VWkxoleh25onKJDDFHoikc8a8eWloSLuuIA4BurE/S6HfUWD4Ye7kI2TPKuWl6xL5GEH2CwucUw4jXGo9gclp3Sxdl/Dm4IbDzwQ2HJ4ADYcnQMPhCdBweAI0HEUCmNbeemxAZARo8RAA5/EhTaz9yM72VY3UY10iIUCLbhp+9FK6SiVPMsch3kXXYaK4aJA9UIgEfmCN5R4aJBNBR9jGU7yVkK9yNaEyHHKEFvvZYggmG0EOVFr8LQZK7LfcQ4OIAC26vML5wFc4wgQ/4jzFGt4QOMq93M8qWzQbmEbpVJFqR+Jw6ps4ySYpnnbIVTzBVbmA62r5E2ksfpV8hMPxPxTxuj0UiGwBVwLfBeBqAL7Lu7hSUvAklzPGfcBuunxUSwA1LgMuBOACTlGsRYyCy1zAKcBrireTC+N/lwGvKcq/AHhTLH+Tf7txRbEHiKDuAZKUx9jKEbZpwyGrewBxffFnpS68v3IPDZJngFW2pIumFxhTBnGJjMDzjHM9VzJeigAH2Cn8Lvob9VvuoUFCgGivgFf4Lr/Feah3DMi8AeaAPcp9rsKN5TC18ZHfNu5P4jhB3+fvNorPq4cN3h+g4fBPyw2HJ0DD4QnQcHgCNBwZAWz7AdSVz/KNVP4Nxb5//Zb3+/oGLa+I5C3Ath9AXbktzFy/5f2+vkHLK+PU1wHcw7WS5DLO5dH4e135HfypJH8LZ6eTzf2W9/v6Bi2vgWgIyCL/55dNvU3xLY+ifDndWnZZmz8w5LeVXyyhH/lt12+rvzn/CWFhmi6/SZ6vhfqqS6IYKlYdDNoWSjZb/bsE7EK9Orhu+S757eWrwmG75g9QLzALS/wOc6XI8oMA7NS2X3L0U9xGT1Zo5Qkg77UbKH/p5Mm4m43H6gbWNZC9/EBZmqsC7OWbCVC/fYL0eDV5suNvpP6eEOC0+kXk8Fru//IIrT2CGfnl6FVKyK98rJI/dMhrM5M9aJDt5XZuJ1N/T9DrIWAB+ADVh4D6Xby+fnIJ1bpwU/luPYith9Kdfy+3C+rvQQ8QPQTa9gNwky8BY4zF3/Ly/E7YoeLokZzUJscoRykX6x9KR58WJDZ51fZJri+sLL9NUL/6rCUREeCQUIEEhxTf8ijK22kDtrX5Q0N+W/nFEvqR33b9tvqb8heDV5WVA0Lnr77qkojmAVa4jLcUJMu5nX3qyh/lt6XNKB/ig2sm7/f1DVpeAxEB4B84g1O4OD56iEX+TEhXV/73nMvpqSvod3gwp561kPf7+gYtrwzvENJweGtgw+EJ0HB4AjQcngANhydAw+EJ0HDkjUHum6cPp9yjAkRr4Ej67bAydV25x9BBHgLqqe6wtYR6d25QuwQPAUUC2BR4mMNGeRKeQQebAnWxvBOEFW39HhoUCTACRgWOMGKURxE69AgxO0yYNnwBu0OFR0nIQ8BIhVLE3OYS6t2/NgJ5lIR+y5jhe8r3bwF9QJn9AoZd7lEBfiKo4fAEaDg8ARoOT4CGwxOg4fAEaDjWLwHafkKoFxAJUH+eLWSKkKm+17vNkhAAwqMiRALsiv8NGra7O1L/8qCruREgEmCJZF3fIGG7u736ewjXHiCkLf0rh1D6UyNSr56Gifr9M0BPIHoELbHMkvLeCoDlwr9ymHZKlah/l1G+7J8BegWRAKYeYFeqmuRfORLMSEfkeP7tXPmq0kX1+0GgBxDXBtYP9B4yzYxyswb5zaCYJq9+VR28+vsA1x6gPuz7d5RTf1uTzqMUhuktIGA5/idDpX7/DNADiENAm2XaQ9m5hnGnX/z0qAkfH6DhWL+2AI+e4P8BepjE/N9O74IAAAAldEVYdGRhdGU6Y3JlYXRlADIwMTYtMDktMTRUMTM6MzI6MzktMDQ6MDB6ohKoAAAAJXRFWHRkYXRlOm1vZGlmeQAyMDE1LTA2LTAxVDEwOjM3OjIxLTA0OjAwKEFuvAAAABl0RVh0U29mdHdhcmUAQWRvYmUgSW1hZ2VSZWFkeXHJZTwAAAAASUVORK5CYII=)}.ui-button:active .ui-icon,.ui-button:focus .ui-icon,.ui-button:hover .ui-icon,.ui-state-active .ui-icon,.ui-state-focus .ui-icon,.ui-state-hover .ui-icon{background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAQAAAADwCAQAAABFnnJAAAAABGdBTUEAALGPC/xhBQAAACBjSFJNAAB6JgAAgIQAAPoAAACA6AAAdTAAAOpgAAA6mAAAF3CculE8AAAAAmJLR0QARaw7li0AAAAHdElNRQffBgEKJRWQ+SdFAAAalUlEQVR42u2da4wlR3XHf207sQjx2iHEXuz1rnASbBIw2RlbEY9IWMi5k0ibAPI6dwcFCDg7DoSnyM7gzPiDZzFzh8T4gaNdyybI0jyy6wCxpfgOxhiZsALM7PKMQxJsZnHYhQ8hLB8iB+HOh+pXdderu++de+d2/Ud3bt8+VdVVdU49us6pU8G1eDQZZw06Ax6DhReAhsMLgIw2Ie1BZ2Iz4QUgizYrwEqTRKDXAjD49tMmrBxzBdiHTgTilAdfxh5CFgBzBxgmfybY2o8+fhg9va0NY3t2zMRqJRDsX41EwJTyCPURWQHoRQe4r0YKcdy4HZZHnbgQELAKrBIQGFKuU8ahQ5CsA8RFjNuBDiEUqicLkU5QKX7cynTPtz07rJl315RtZdxCSHsAcwfoClMbtA8f4ukmFppTqdc2TUNQNuV6/cyQISi9EmhuRaY2mFZq1bZjT8HcNs15N/eBacq2fmZLobwAmBEOvGrarFQWMPMQFKc8+DL2EL0WgK2ONiujxF47vAA0HH4lsOHwAtBweAFoOLwANBxeABoOLwANhxeAhsPbA+TjDjr/m4wy9gBuFgE2ZUzbaA9gfoKdPXXsAezqcJH3kRKScvYAbhowcxXqGbRPc+2ato39ttRXct/61EfGGqBoDyCgXw2PQ5n0bXq6LbaLPYApd+an2+ObEUZpx98jAdkeQHUtY9WpF1CHsbdPF3sAU/tzy5tefEKrtUGZJ20JVFEGmRSuw24PYBIuW/8Tl9yrgw0YfOXUtQcYdP43GV4d3HD4haCGwwtAw+EFoOHwAtBweAFoOLwANBxeABqOcwadgaFDOMBV/vprpaXzf0696H2phEHmILTmoLoqyB5zACWXh4AQjLp+F/8AYQVKWVR9hi3/gvWBMRW7cFSN7VYCl1Al4p4lBbAVP3AogD5+4FBBLkUIDcoel/wFBpr8Xe4ZMcVeA+YSmgUotMQGWyOW8p8dAlyLr7PWsVdS0IMOPjRqIm2jaJ0chEnsQEnNPl31lLh56fMQGujmtNPSmZtBNpcBlJ0Ehg6txxbKRTqrtXE35gYOqZsY5JJu1RowNUGXtO11UKCXeQ1MuziXUGqauQu0S7A5DVsX69ZF21qQ7ekuk8iqsIu4nS7loEwP4NZ11pvlBo69TL/yGBg7WLd0A4cwVWEeps0DoDLuOZpAg8Ogc7CVn18hrl8JbDi8ADQcXgAaDi8ADYcXgIbDC0DD4QWg4ZA3h8bOUgcHuz/wfsKlBlw0otXi2fZGuz6lFFIBiDdGubh7r1YBvUO1tGw5d6sBk6vZVBvXLh1b6CnjP30Z2pVrIMzlElBvDjVv4XTRaLcV93onArq03FxD6PPvVgO6Z7Rz22vbpWKnJbD1QPW2phc26Mpbw1zcqdu2YOs2iLpZ0thzoEvH7sLdnnM3h/RqjUGRtUGObttYnjJHtT8xlFI2K4x1CuugGKasALhXQFAirlsOzFXo8nz73n79822xbQJgrwMzA+0CYBYgjQCUewtIK6CKyiLIpKFOPZS+Tc+vgjTfVecQpqfvi6jxCK72IGB6fhxTPQewpZz6bjDtb87nsqQ9gKkC5AmMqfjmzJmKaEojWzS72ZeKBXYBNJVgNedAYrV0Cm4wsXc1OfbGLZeUHQLczKlCq4sI8yhYJ7Zb9arL4TYG1zdpM6VT/VAb+xxACe8fIIu29cSkkYMXgIbDLwU3HF4AGg4vAA2HF4CGwwtAw+EFoNcYpDq7AvL2ADaY9FUuRW/X1Hf3G/VzF1gWu4es7EV7ABNMGnOXVcJYY7fPYYOpHnU3V5m3hwfW7a92Buvim1IfENKFoGy27N5+i4uN2a2R1U7/dl1oBpPGzhY70IbL3tVpO02bR0MnqntJNwXqOYDO6MCsr0qHhipGC6Ll2M2m9D4MQlx1fUGJu6rnqp5v39k8lMifF5BWYdkTuPNDSFAibkx12wJt37xd3YWEiY22HsI9ZZOPgE1G2gNkFYVVsmY7ScCubK07OgaZHkTdQ8jfqhC9acWqJ8i9x5CwXx4CVpNMqTpw0cELcy81Vo32AC7afrt7CDNSWwC1SYW56tNBSO9dJA4ZlKRmQ1Q1qOkL1NrAUNuBuyhLdZPAXihb3awWq040XSaRgEVAh4a5LvDqYBlD0zVvFvxKoIyGsd8LQOPhBaDh8ALQcHgBaDi8ADQcwycAreHSlo068gLgpss2qWxCJ6ouRIvupryKDdoPwtCgnLt4F3fSARM18tMlFpKWMVxVl/UpRugE8DqQBcC8Sm1e7Y5bdYuuUgTCZKFUvXdPdP0TSYiuJn58Vc2perb3cTtqfsSRCoDs7r2IVB+uc5keEETsX1M+y9y1i65/jQnD3tn46ernyxYF+VTc3Ec0DrGv4LTKzB6vbZqsmP3Vx/E1J1fOOm29ziIgtlZI6SN0BHwdZE3Cgtx/FfSmDG4GEXqjspge9x86kwx1Dm3uE+TWP2JHwNdB6i08W2V6ByP2Uy9cj5XQ0YUIhIV5RKwIVnvll/PTK7fyDUCZt4C0inU2ebYjmUz0iYTaBYLCPCLIPF01EJntiWT3ER4J5PMCbJZqJrPLuidZrCVpu7xGBo73YqziZ/1KDJtBSKh9h/DoC4bt5FDfPW8yhk8X4LGp8ALQcHgBaDi8ADQcoyQAs8lKw2xf0r+MsejvskEXtXcQAnAoqrgNDlVO6VGLpt+GkCcka4GyTJxlPrmeV8aerSUel/EU17LOOtfylFIEZq253x9R92ueoafbYsK9uT/zExIuiXWAkId4EjifqUzg9JXsUHL/MDdqkk4XiY6y17CzqJi6wBJPZlgIy7xJqtz5XPg5DpagyzlU5W4/h6XfU9wj/R7jWhYYB9aZ4RGOa2tA/QwXZ9L6kz9th2KLEGnN28qYLPnFArAIwOek4GuZxIsCcpJdmuo9CkoRCBlPrtcVRfwqV2V+ywIgNAGTCS2/RSxkThKBOea1+3d1yqxx6Xc+h2OsM84O4GV8iHGNAJwC4EUVdxiFxEvagTMlG8IsAHkRDyBdCIpZ380HiPAkcIIf8ylD9sei773aENsMsZd5UhKAPA5L278PS30VwEFIRGCOg7keIa1AfUVu47Hk+hplHnZwEQHPN+TyLw00cw9oVscHilTKiVjM/r/hA9nb6Upg15LACX5cCCNn4YWRLi9U2PMI/Koh/Um+anz+46Qq48M8XhCAVASKnb9AK/ddzN11xpzO8E/cCbybGWX808DTmesi5phPPpuLmP338TxZBFyXglXsz+MFAJzFc9oQFwBoJii2HiAWATjM49owAWgneVfnvvPYxsejq7cpqJfQARaAGTrsKQwBeU1q1W2mdi8JthCf4K2Fe4L9R3ke8E6AaNAvoQsosj9fwAusafxScjVeoNl6ALgsYvzjXMZTCvosT3EIeJxZTR9gxi/z7uQqjza7eJD9zABnEzLD8w0GJXMcVDJpV+ajwxg22EK8RSEAUxwG9nI0mkctMi0I1ZVBRfl+vjXOndH3uIJm6wEE04UIqF7DZiW6qhfYkftWVRHMINq5PMTsYgEy7wULmmFAYL5GF79eM4TapuMeiEQAMuw3CcBc5rrY6RTZ/zn+RvpVhLlLNPcAc4rXvDJ0iIeo9DtfRfcAIb/AfOEVUIhE/k4nVzrbJA9uyHyKWE7ecmC5Ygg9YhGQ2D9M9gCzwEszv5+s1I3XRQgK9vcydYHBqL33c1hm/zAJgMdAMEq6AI8K8ALQcHgBaDi8ADQcXgBGC49l9BlOkAWg5bAxWw+XkzfdMKvUqM9ldNnFt/xDhNJf3rLhSI5+RPHcrLZ8fx/oAJ+31E8nt75QBq+N/sxYYoml+Ef2NbBFlzlgXmGbv8EbohWoR3mEFzOlVOc+zV7gKC/mqpyyFtzffWPdvhx+jluiuyK1mxX6vqPJr72F+K76eLHCt9AXehwmAJYkdTdAhwNM0AUm6Obf12nRBY5yPUfYC8r9E99nB/AMlxpqdylaTFrmc9yXFQDBfqFNK4pAyD6LN3DbWqHYT/hJ3sgneSMPsUdTQbMc5BBTBZ1eeuSq+vBVl+Pb/4tL+CEX8Qw7NJtPZ+gQEjDNgpYOGOhf5gzb+F0lPa7+ZWCyZA3G1KOJuj1LP1JQwh/lesXzDzHFMvfTje0tsurgeDl1nrlKjlqyW7rUmsNb+B4bnOAU6/xAGWKWeXZwI8/0YR3waS7mu1zId7mE72lDibX0GSMdWacu4QzHteqauPVNKqkTUq3pNsiprS1+zeEOwB8A5/FmAFqspQLwhLSaPs8cT2jVpjqsYXPmfDMPsYfP8Pt8ntcqjMtmmecwU31hP7yYf+W3+A9+k2/wVoVK5V1AbCw1rYgf0wEDfRtjGsOXJYnx+bX8DgeS9MUW2UXlU9S4hn/h1ZnfX1SYtLwd2AnsIWNvFQvA1cTGFOL7YF9YcAvf47/5Eqf4EhsFasz+OeOzQ4M+fCJxT6Pqgb7NS/kWv8G3+O10EpSgzZ3E+v5phfInpZ/Nzw30dA4gIx17Bb5Qsu4mcmXK9xCvkWrlNdrn5xpodhIYt161Tdo4+7mRt0fmHEXpDKW4xRG2aLYZFOgm9uddQKjGyFgA1pT0t/NBZriN9/Nh/o6PSvTJgkjIKqG69JT9+alfilZuCFgz0HXUZxDq7jx9iclo7M/ZcroLgJuX/hbxUFB2DiEYrG/98VtADNVbwETiokYtIDKK7ykf4G+NuatDDwiN7LdPo1MRUL0B3MZ7eYDrgSNcx+28X6IuMclD/JTJfNy8k6j0Xb4sjhIS0qVLGFkG64uoS93U+c9zc+bXzYX+ZArR8XejMkwp6KbfsE/Lvvr0ZSv7hZGW6NgnSEy2JKwxAZoN9D/j49G8/3o+zs8UIfYwyXI+rqs6eLrG8oRHGXSgxOTPHWKIKoigtwdoOLwuoOHwAtBweAFoOLwANBzNEwChNla903QSVe67HNI5T3l36I6HtyErANNJBVR/DanuH6AuWoTJdq3jWquGz0bv/wcKIvARDnAP9/AO3sGdvLcQU9TOg9Gv84Dzoj+Bm/gYIbdwCyEf46ZCfLP7irw1Q96eoUi3hSh6epDpEdLXwGkWOMnDwFs5N1F7FhOxnbIN/bJ6X2KSGTpMs6BYVBFPPsEYx9mtyUW8IHsD91JcKXxlcn2GbyvWQk/wFaaYoROlIy+H29Xh8ep9V6lINq+9qtxndnMhgsRQZl7h8jNkIhMjUWen6uCFaJX4OOfybGHfyzBgEljgSiaByYIAnGA3sDth/wlFChdF3+rtqU/xi/wEOJ//U9K/wo1M8YJEp1++n7w6Wr8MUa16zjKf7CpUNaE1HsxYURR7OCGCV2aui/hTfg7A9+Mb2SHgYeA4uznBJ0oXzf1IGVNsZSeVQOjZJjPXWYxFLI/ZX9TJt3idMQ//y08A+AmvV1CPMUUItCP2F5d1xzN/asxrrkX+54F5xhhnXGlR0GIPcAih2C3C7O47oMsMO9jFpVya2gzJewMF+8eUnoLC3FU1ZY8pizZ0otYPy8r+aSzT+lXs70o2D/m19m9zJuMI51gh/qvpAAfYiU6nt40zpcuU4pLk+0HgjxQh/goQOowphN5PRkgqVsXmMwv8APg5Z7ODW3lU3M6eF/As50ZVt8HOCiZfGEO4GTyZnpDV0qvmKF+Puj8o2sXJ7FcxcJo/yfy6m/sMT1cJmHCNIQaPM0oXOBPSqJ0f42+Q7ofcV5gDZJXFJ/hg6TnATRBZYSyltZsOATOcy7N8hUNssFPRxaaO1tUu17N3VSGC3J+ZqnrCQsS89DqLmP1iINiRjnJAavC2yASBsv12eIDd0V+R/bDACR4CHkXMNIpY4zN8nvM4V2mONWdxsHEBF3AvF/Ar0X8zdivuxXOAK1E3qF2czS52sQu4KQ6RDgHC/4XoBGeGcAooNkfP0OEbLCg2Rwv2P8NYZBub9wIg2G+auN3KdfwncLGC/QCPME3IOh+hy26t5d9DmtQPZpxG7C/sPz4cba5P/x/OhdiR21Re9HKQtZRSW00pPCOU1QYO8jXQjBbdpOP/PjtyWnP1vFude3X+xfziWf6YtcgwYxs/zcVd5d95klVtLYUEyX6BwwUvZH/IfGSSN8c/5/qYQwr7BdllXz5E0aGf0n+BVwdnsYe/Bj6kacVLnMfdkVi1OMarCiKWhUoAsmZxdnHcFHgBaDiapwvwkOAFoOHwAtBw5AXgkNZf+F18LVmk/Rp3DTrjHr2BvBT8b1wOvJYrCuE+Ja2Pv4JXsIM3DDrzHvWR7QHu4HIALueOXKi7EvanK3SvV/YCpwgjj9kq/E/Ug9iXmYZxIepURlF1qn5yw4GsALSACSYoqhpfpYyrurs9+qhxfvR9wJKrjsJgA5aiyl/SxrOFsNFDTiXmGkUWv0hzvaWRCoBo/2usUewD0kXPrJrW7tU2j4DA4VxQsU82LwLp5sZJDQNtIZaY5A7GuUObAmxnPhISvRiPFNKFIDH+TyA2WH1HmgfIHi5N/i6PsFfjmkBALKKeVLhL7kTr9PE26fy6vd0Rawgscz9vZlIZIuSOyNTrdt6jTeF0wvoyJ3psWcQ9QCca/7uRzuryiqPw06Q+81XoAj9S+M+JO30d+11xP2vcb6DK3ylcTFhmgdOc5jT06ViqASDuAbJqkKJKxL0HsEHs4c1vbkzZrmf/4HuAU5lh4fSozAJED5C29lZmApje/bIyrupuxzLHDxQHw8N0ZJ9jav3Lmmv57iTdxAtPkf4ebmeM23mPwdf2difKyMwQ4kOjNNTo+zbep6B+NLcHPU1J3zPo1cn2zt/uZMEWwkYPOc3dkZbulKaNVz0JZEghBOCUUqKz3dwK7Rx1lX2KOB0OGMdvkz2BLe5wYCQFwAUL/F7y5n+MLxhPzBhlNFYAPEYSXhvYcHgBaDi8ADQcXgAaDi8ADYcXgDw6Rp1Ax6ox2GLICkDIhkUF1LsjIQaFJ3jCSO8YbRU6VkuGLQe5B9jJAasQqJEKT0ubQoeNSNPQYaMgQrL4HVHQj0gpqURQv7U8jncVVxnK585+F6umLYG8r2CBk6wql2T13oRDKV5Ifk1fVF4AdGizUzzbkMIR9hbows5AF18ugf60Dh1VdkZtp47IiqBaAEB94oRNACA29pCVQumvjYh5WFLQCYA+vpxGL1isp4aK7ddbFOpJ4EkWDVY9epxkMWH/YqaCAhaju7tY5KRDCjrY4m8ORoL1AkUBECwor5OL47XYYLFw5sY0AYts0GJay0S3J09XFgKT7wFBXTTGzVJDQ9gtBXkI0I39aQj9iQLDD3MnL5DOVcpTtySyG0PsBQucQw4jXHI9jclo3UzdkvDq4IbDrwQ2HF4AGg4vAA2HF4CGwwtAw5EXANPeW48RRCoALT4NwIW8TeNrX+jZPquhemxJxALQopu4H72crpLJMyxyjNfRdVgozitkj+Q8gR/ZZLqHBvFC0HF28yVeSchnuZZQ6Q5ZoMU97LQ6ky26Ks7/lh0l9pvuoYEQgBZdfsRFwCMcZ5ofcqFiD28InOBu7mODnZoDTEU4la/q8cid+jbOsK3gTzvkGh7jmozDdTX9scQXv4o+znr0QeGv20MBoQu4GvgmAKJD+Cav4+oCg2e4kknuBfbT5Z1aAVDjCuBiALZzlmIvonAus52zgOcUbycXR58rgOcU6W8HXhLRX+LfblwhBOAJ4OWZuy+P7snoAPfT5WZ2cYI9yvT0ZhIXSr8+Gnm2T7Gd92XEoki/kPdFH1N8EWa7gu6hRDwH2GBnsml6iUmlExehBD7EFDdwNVNaf9iqIeAIe6XfeXujftM9NIgFQJyH8SO+ycu5EPWJAak1wCJwQHnOVThaBlOjj+yxcX8W+Qn6Dn8/KjavHjZ4e4CGw8+WGw4vAA2HF4CGwwtAw5EKgO08gLr0Bb6Y0L+oOPev3/R+l2/Q9IqI3wI+VTgv99PSeQB16TY3c/2m97t8g6ZXxtm/DnAXby5QruCFPBxd16Xfxp8X6C/j/ESb0G96v8s3aHoNiCEg9fyf3Tb1KsVVFnn6anK07Ko2fmCIb0s/n0I/4tvKb8u/Of5paWOaLr6Jns2FutQlkXcVq3YGbXMlm+7+XQH2od4dXDd9l/j29FXusF3jB6g3mIUlfoeZVIr0owDs1dZffPeD3EpPdmiptobli5mno6GH0bhbHI/z6YSa++b07QWOeyBb7EArci6p6/Lnkn6I2bPAdcYc3MStGfb3BOfUTyKD5zL/yyO09ghm9IbB+gZgz789rk1N9oCBdhMf5sP0lP29HwKWgDdRfQio38Xr81dMoVoXbkrflL/i+Qvl6EIEsuzvwRAgJoG28wDc6CvAJJPRVZaePQk7VNw9nqHa6BjpKOly/sPC3S9LFBu9av3E5Qsr02+V2K9+akkIATgmZSDGMcVVFnl6O6nAtjZ+aIhvSz+fQj/i28pvy78pft55VVk6IHX+6lKXhFgHWOMKXpajrGZO9qlLf5jfKRxG+Wnesmn0fpdv0PQaEAIA/8jzOItLo7vHWOYvpHB16f/ACzk3sfn7Og9k2LMZ9H6Xb9D0yvAGIQ2H1wY2HF4AGg4vAA2HF4CGwwtAw+EFoOHIKoNsp/MOO92jAmRt4Hhyta4MXZfuMXQoDgH1WLduTaFeyw1qp+AhIS8ANgaus26kx+4ZdLAxUOfLO0ZYUdfvoUFeAMbByMBxxo104aFDjxCzwYTpwBewG1R4lERxCBivkIoc25xCvfZrEyCPktAfGTN8s3z/FtAHlDkvYNjpHhXgF4IaDi8ADYcXgIbDC0DD4QWg4fAC0HBsXQFo+wWhXkAWgPrrbCGzhMz2Pd9tViQHEB4VIQvAvugzaNhat2D/6qCzOQqQBWCFeF/fIGFr3Z79PYRrDxDSLnzKISz8qSHYqxfDmP1+DtATyBZBK6yyomxbAbCa+5SDm/v2mP37jPRVPwfoFWQBMPUA+xLWxJ9yQjBfuFM80qWdSV+Vusx+Pwj0APLewPqO3kPmmFee11N8M8iHybJflQfP/j7AtQeoD/sRTuXY39aE8yiFYXoLCFiNPkWo2O/nAD2APAS0WaU9lJ1rGHX6+W+PmvD+ARqOrasL8OgJ/h+DVadYm94w9wAAACV0RVh0ZGF0ZTpjcmVhdGUAMjAxNi0wOS0xNFQxMzozMjozOS0wNDowMHqiEqgAAAAldEVYdGRhdGU6bW9kaWZ5ADIwMTUtMDYtMDFUMTA6Mzc6MjEtMDQ6MDAoQW68AAAAGXRFWHRTb2Z0d2FyZQBBZG9iZSBJbWFnZVJlYWR5ccllPAAAAABJRU5ErkJggg==)}.ui-button .ui-state-highlight.ui-icon,.ui-state-highlight .ui-icon{background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAQAAAADwCAMAAADYSUr5AAAABGdBTUEAALGPC/xhBQAAACBjSFJNAAB6JgAAgIQAAPoAAACA6AAAdTAAAOpgAAA6mAAAF3CculE8AAABLFBMVEUug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8ug/8p2Tp3AAAAY3RSTlMAWEd8IjKY4b3Ld2acsomqpVpOeudAQGVmhVOLRpGUY2NhTaBobXqbc6W/fcC8463l6eSBjl3f3eC51tvSxNXU12LacP4Nzplp+DgqFhzFedHjp4FYyJPQ2K/wzZCniLC7x6vHwZbrAAAAAWJLR0QAiAUdSAAAAAd0SU1FB98GAQolFZD5J0UAAA+BSURBVHja7V0LYxvFEd67iyQsxycZJGgDCYrBKSR1WjdJX5RCGiJICzFpmxCamFLm//+H7t5rZ2f2oeNk6Wzv58T23D7nu9m9md09WYiIiIgeIIFk213Ysv7QcwY6dy8Bv/4JZkBl3iwhxAJBwSSA9sdIV6kJvgLAGgBPA6R88etGTYJaICcgof0x0ukdZATQ4rwBljnZIAOs/3YVPOmcQUFy+2u3ZU68mdYKZsG8i/QGcwvx3mFuAZ4ObN4C7KSwLvoIYKWBmYindmKCm58DVuDjTJ8CdAht/imwdVx2RygiIiIiIiKixzhzT3DLflDCojWgzntCS9DsRoCfsAZ86wFsQUjWvlFKLB1gBLAMNLsZLiasAUqAJ7pUtW8yGGL9t/fYk2xZUUk8xUVgCRAKAja2HMAtWNhs1ojWVlgPSMzafCNq2xZgReLpcff1AD5CtjoHhHHRnwIREREREREREdtDN8c/6JoG6+8ceHSsAPh2KrTI3bl//DgA61CgNvBf4eqRZOBZzOLgSrM34O2AJdXfvq0GH0EsnVXGNODNAUkER2LNKKuPFABX4grt83AZQgTwBSDwaxAu7sliKljlJmtWZnZaoZc/aw6vCXkHkLBZCGHcUtxvouEW2qgXHOOWM0TgTw/USG4HBG9IoAEQ1jbdqdt+Cpxx+fBjMiIiIiIiIuKyovux1I5uRmI5je6u0uaHBreqAs2368BKDfjjeba3aukAShd4c2oFr05ldgcnYN3e551kVbrbt8S3VAFf3WC9qYgfgbcneW8th90TLwGBs+HCamY+Brz8JZblnsDygxHO1uFwfYHtnRMLYuGwJRpnr2yIFTpgT7UyTGqn5S024C7OCGA94N0z0+kQCxNg74DzFq6UzAJmNwHWvXW+Q++8AWwIkCESHAL2UZ44czCGvYcDeB6LgQmzAsF26AMEkEmQpLJpKbSCQ9u33CN/sr0XDgJXCd4DFsAz93s9YNvvx0RERERERPQaZ/sU544KeVXWUmK9jkW4OmiXvaX+wK/g6M9aArO20n450ZhmBqfIdnb8G1/tAey0uOk7lnuTnrfDA66+JQMwhYURfXoJAXudXQlwv99dJHk+H8C2nmHuV7P++oKDuiy4iq+dgDrcdBGQWMJh3nVPPMXTbbvTQFLBnxnWSEFi6SELdwGbKHjHsKU2uiDiPbNiJYAOibWHd3pSU4sJLDoz3++3pBPBNuwxIYyfACEhwrvDXNFh0Sl5YyQQvYYOAYXWH/zrRxcQF12/iIiIiIiLjfScP8gsbgf4tquoN/xz9O/TVoB1m8X0vtLgbiCkpFKvKESvNkPY0WWB4hWlagopCobM+C6F0gJ0fmHdAmcE9mXYAI9e6PF6qb8RnRkEQEmCEc9SEeubQL8IsGy/c4JSIlMC8E9hid3QtaQZYn0ZAitYAMtvntgoCXJYAD2vUNPdG/2ZjmwOIDmsKzSpthI6B1gOyPTG/HWfDAn/cEz5KH9qVwgsvyls8LMyWzDA6Wh3k+gz0IekhwR0RRv9IyIiIiIuFzLlJ2Sr578ykLiyqd4NZedGQ1+ONwKeG+yUrpJLxYwmZ34+rogxwFhcIRWgErtS3BUOmSaKqxVIgVol2MvzIXL2it8NQgq3aMJPP9fitNJwaujb9JjKbGdrt0qvez0Yw2AA44HRAcGCCXrW1iqUFya2FpsgLc/ztAQhZGQQgBgAZaID3eKOQYCsel+icaWhtgDXfndZna5wAIM333wLMAGz2cz/BobABIgAAbsGgaBURxckIQkmpOygSfh8/vZ87rIAGAL6oRqu5gBAHTR6PC+KzzUBb77zi18aBFy7do0dj3fL5AIlQOn/LibANCmQ+ps2Bu+l6gs1eE3BaQH7SnUY7ut1gKyw/4YAVT9aYiur0xXKIXD9Oh4CMyFvgfzeFMiKr59JgNL/6o133QQk5IK8kiT7CQph4P3Fwj0HwL5kQOqPCSj+NQQUkyAi4KYqffNmfeGgnAQPiDqoACeAvaIhCAEf4PWJyfSq/J67CKANwocFUIOHh4egTZRZQLY/HMpveggUspuAwxLVhWQM74zHt2CM3xFCQ0he+FXxhfUdUAIGhAAwLGCi9fcQ0FT3UQFicoOGAGoB2X6B+hYxGdQcOwRjTI7HzVNgXLc/dloAJyA0BHB6OQfmTeaGgMxsr6mu9APgDeEAsQD62MtY/ZPyHuAqMv3oBq5wYNL7uBA/Fo4LlICCgVysD1k2LdDC12Mcmq5LODu0Wq6h2F2r/hERERERPcft2/70FLzr2gC2o48EmQ537xSPqTu1WAXbTYw9qeRJU7Z0TXZXloX4NelP7n2uyWhrTi7JxzbWP8s0AyPlRR6Nh9oP2ZFdnuw0jpyVikxfv1O54jUDsrAC2WkyPZuxcgVXlsv70WiQK2cubZ7tqeJ2gu/pXYC7RH/luC20/so3b6JfejqcOWYCfiO/9nCHMnmfM5Tf2BuksYX4rTgWv8Px7VgKY0MWpvz24G0kq/5Pp64OQuXsV3JtcMjiZGenae251isWTXTFCShXBxAB927ef3DjJlo2yqR9Z7g/XgJ+D3+QX3/ECirXn8g4+JCx8QClT80OVs58am/vdi2ieWAEe1PJQSnsVM56tuMioJoFkAXswZ/gtu6Q1B8t2YUt4M/iE/EXvaR0SCzgkFjAobKAuZanRuwhR0A5STXxLWnv01L6tOlgEcxrAygC1AzpGybg3s0PPpRfdv0rTx0TkEKx6lTLf4XP5Nfn6MSEMcYL+S0io/Ri/Ep86CCgju5So0PEfgSGOcvDYCgWRrxICMgIw0T/5kSESQCSH35ybXTtb48qeb+ubnc1eWrePcGGQCVj8e5dLSvbb9Y7rQQIAnlBrQ+6j9CQRe47VYf1U0AdMRKuIaGGO6nOLwuiPw/gU6y/uP+FnP4mX9xvCJDjP/WUZ4pO2CRqLrKyRX7iB9BlbyLbPgHGJ0+p/vQxKMpDXTq52BG4mjflgdVgYCzOIfIWAb7hA0VEREREbAFDvDCtXDk4ZHke61/P+GhhsRXhffpBlx6ksJTfl/jRfATI1XwXvvzyq6/gEerOntK/gPzl1g24dw9u3KrTy9gNc1liSGR6oQneqN80htFw+MRgwP/hYiFMZV1jFG2CZGBJvfGF9rz+rvAP7Youh7KCKQtumnQjNmUvWVfBq84jXcdMBjt6c7BM0MGVcoyX8MRyWvZnEqBcLVRC6V78Nw1AE/D1N48ff/O17s9QQD7V7honoIxG6p2mYjEKHXhIRblUkWpfO1PrMYiAB2qvDje4VKy7CKDhJVeXpJe7e9qiloWs9U/N/FDY+m5T/KlMGiF3FQbkQIZZvtgHRRlABZ4ynhPYAiYTfF59fHKiwktNgNRfoCUwyjgNFuwiMfGm/7UNIP3LO1jPAZ/BrgQ8bTLkuVEe5n4CDuSvB+pfnawMbAgLZAEken3wYP/BCRw1FT5RvRutjwBqAd8W8jNTf63geFlgYRbXhEH63nw+Nwio7mz5Y7FYvP9wsXhIDjwsnXPAyYkaAHgSfDIcjtY4CZI54NtqDqgYUPrnRjh6S/V3oYsv9+AIMaAqOkDTXgYmAR99VP0jBuKcA4bZyckJnGAG6GNw3U+BZ+IZjv9p6LacTPSClZwB5b9UMwDGj/rX3foCfQwqiyjhmANgqIAJsN3DLgQQpMW9f1b7AZYzguYMK63lSapmysd16j//9W/zY11EMWtU0iBTS3pZfWCjvR+wfRw8f36AxOme4ip93DBGO2w8BiMiIiI6Y4hPR7/4Tk0x373Ydqc2iJcALxvh+3rW/X7b3doYrit1r1fCi/KJo75rG5jBDBf4j8WZEes7eTYr+J91r2hVvFQBVG0CrzQBr5ocxG2w+RG5poRtPdALVIaZeqbPvPWfIa6XCl9HjVPXg/UnpRdybRTl5i1SkF6YwuvBa3N3ljW3SQLkDKBC6JdG42YfJnhjrNRfby/mpv62o7vTdIr1ey2/vTYyzLZIQF7f79xNQE6GPMBxitOw/jYCUsNkioPmAyOcNgjIYDabbc7T1Qq7CeBlkP5Sd2NS7GwBm50ECwMoX5opdHiuCXiOMuX+CnB65zlgs9EanfTua/E+zkQKEQYMfjo/BYTY4BQ40wqXPTitxVOsI50DsJSv//T5VoP1H9SyLDz9YZt96NNqRURERERExBkjB5941oARcWRWekOiC3Z2qP7gEc+eACAUGAQUaSnOkI9S9c3IoELmWp6UmdzhbU5855wlQ7FDtkECTApMAsq0ps/F7ZHq0QwGATidE0CDRb4YYB7G3QgB+DAwJaBY/qg6WfwY4T5XGTABI4tOYY0NcZ1/P2AlAjZoASsRsGEL2OwcQLH1OWDDTwG+3rHlp0APsF0/ICIiIiLicsP/HtlFR/pfAT8+RGc3pZdydIk+J1e9Rwo/5uh9hnH+1PICRe2b0M8/aCv3Dkv4nyRAoNPJipURY4C+WarP67eT+4YUjoX4MRfH+G3r5UJGtOb7tVqRwXwg/zXHt2FunmdXMpjyQH0NeureZtW5+SN9h8ZTUKft9xwEFB+NluzXn68HCSSJulDL++pLf/6eSpdXkv2eElBYgMQxvuNqXlgap5MRAY9KNCbeUu4dRsUzcIrOvMhgdAiLoYOACzcJjgGOj47xtF8uR+iQFNb8Fy77hvFLeX9ensu35iMiIiIiOoO+HxCS6SGqtnLb9rrKIdD3A0IyPUbXVm7bXlc5eP+hwYtVZHqQsq3ctr2uchD0/YBXuoJaPlW+4Wkll0dpi/TnjQxUFs70Vzr9lbN9Ad50daKTpAvaf4Hfd/ABdAPQyHUlotoNPj3Fu8Oh/Dyd5ddb5LZ0vHtm/wlGf8RPP/0kzP4IcbLi/hqgd3odshq9p6TDuEMsv2AK+fMTAoL9EfV/h3xS6r8+AqboM+gsBNh+tlEo2L7FQnwWcCJK/VcmIDwE1KdvtTHx0BCBEIHeISVIfipLBk6a/EHQ9wMsk1o9CepJjE5SQGX3pGqdJGn7dJI102t+XLIaA40cxKYfY10fo23lMDbtyHR1pNrKYWzale3qSreVIyIiIiIiIjyoHIczk3sP8vcDw/IFJAD8BBRfWEHhJ0DQP3rYb5QfSQgemRAE9TeXTP78Xd8RLeDSzwGX/SkQERERERERsW4k58cTCJ6ChKz9QdeE/H2gPiMRgb6uQAC93+dJ/3VYANX3XOlvWkBxvL34chDQ7L2Z+hocqtIXdg7Iapj64zte6n9+bKCrBZT5z6/+XS3g3Ovf9Sng0P/CzgEBaP3Pjw0ELaANlN71/4iInuP/VPKCJpghgS4AAAAldEVYdGRhdGU6Y3JlYXRlADIwMTYtMDktMTRUMTM6MzI6MzktMDQ6MDB6ohKoAAAAJXRFWHRkYXRlOm1vZGlmeQAyMDE1LTA2LTAxVDEwOjM3OjIxLTA0OjAwKEFuvAAAABl0RVh0U29mdHdhcmUAQWRvYmUgSW1hZ2VSZWFkeXHJZTwAAAAASUVORK5CYII=)}.ui-state-error .ui-icon,.ui-state-error-text .ui-icon{background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAQAAAADwCAMAAADYSUr5AAAABGdBTUEAALGPC/xhBQAAACBjSFJNAAB6JgAAgIQAAPoAAACA6AAAdTAAAOpgAAA6mAAAF3CculE8AAABLFBMVEXNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgrNCgoYgUqcAAAAY3RSTlMAWEd8IjKY4b3Ld2acsomqpVpOeudAQGVmhVOLRpGUY2NhTaBobXqbc6W/fcC8463l6eSBjl3f3eC51tvSxNXU12LacP4Nzplp+DgqFhzFedHjp4FYyJPQ2K/wzZCniLC7x6vHwZbrAAAAAWJLR0QAiAUdSAAAAAd0SU1FB98GAQolFZD5J0UAAA+BSURBVHja7V0LYxvFEd67iyQsxycZJGgDCYrBKSR1WjdJX5RCGiJICzFpmxCamFLm//+H7t5rZ2f2oeNk6Wzv58T23D7nu9m9md09WYiIiIgeIIFk213Ysv7QcwY6dy8Bv/4JZkBl3iwhxAJBwSSA9sdIV6kJvgLAGgBPA6R88etGTYJaICcgof0x0ukdZATQ4rwBljnZIAOs/3YVPOmcQUFy+2u3ZU68mdYKZsG8i/QGcwvx3mFuAZ4ObN4C7KSwLvoIYKWBmYindmKCm58DVuDjTJ8CdAht/imwdVx2RygiIiIiIiKixzhzT3DLflDCojWgzntCS9DsRoCfsAZ86wFsQUjWvlFKLB1gBLAMNLsZLiasAUqAJ7pUtW8yGGL9t/fYk2xZUUk8xUVgCRAKAja2HMAtWNhs1ojWVlgPSMzafCNq2xZgReLpcff1AD5CtjoHhHHRnwIREREREREREdtDN8c/6JoG6+8ceHSsAPh2KrTI3bl//DgA61CgNvBf4eqRZOBZzOLgSrM34O2AJdXfvq0GH0EsnVXGNODNAUkER2LNKKuPFABX4grt83AZQgTwBSDwaxAu7sliKljlJmtWZnZaoZc/aw6vCXkHkLBZCGHcUtxvouEW2qgXHOOWM0TgTw/USG4HBG9IoAEQ1jbdqdt+Cpxx+fBjMiIiIiIiIuKyovux1I5uRmI5je6u0uaHBreqAs2368BKDfjjeba3aukAShd4c2oFr05ldgcnYN3e551kVbrbt8S3VAFf3WC9qYgfgbcneW8th90TLwGBs+HCamY+Brz8JZblnsDygxHO1uFwfYHtnRMLYuGwJRpnr2yIFTpgT7UyTGqn5S024C7OCGA94N0z0+kQCxNg74DzFq6UzAJmNwHWvXW+Q++8AWwIkCESHAL2UZ44czCGvYcDeB6LgQmzAsF26AMEkEmQpLJpKbSCQ9u33CN/sr0XDgJXCd4DFsAz93s9YNvvx0RERERERPQaZ/sU544KeVXWUmK9jkW4OmiXvaX+wK/g6M9aArO20n450ZhmBqfIdnb8G1/tAey0uOk7lnuTnrfDA66+JQMwhYURfXoJAXudXQlwv99dJHk+H8C2nmHuV7P++oKDuiy4iq+dgDrcdBGQWMJh3nVPPMXTbbvTQFLBnxnWSEFi6SELdwGbKHjHsKU2uiDiPbNiJYAOibWHd3pSU4sJLDoz3++3pBPBNuwxIYyfACEhwrvDXNFh0Sl5YyQQvYYOAYXWH/zrRxcQF12/iIiIiIiLjfScP8gsbgf4tquoN/xz9O/TVoB1m8X0vtLgbiCkpFKvKESvNkPY0WWB4hWlagopCobM+C6F0gJ0fmHdAmcE9mXYAI9e6PF6qb8RnRkEQEmCEc9SEeubQL8IsGy/c4JSIlMC8E9hid3QtaQZYn0ZAitYAMtvntgoCXJYAD2vUNPdG/2ZjmwOIDmsKzSpthI6B1gOyPTG/HWfDAn/cEz5KH9qVwgsvyls8LMyWzDA6Wh3k+gz0IekhwR0RRv9IyIiIiIuFzLlJ2Sr578ykLiyqd4NZedGQ1+ONwKeG+yUrpJLxYwmZ34+rogxwFhcIRWgErtS3BUOmSaKqxVIgVol2MvzIXL2it8NQgq3aMJPP9fitNJwaujb9JjKbGdrt0qvez0Yw2AA44HRAcGCCXrW1iqUFya2FpsgLc/ztAQhZGQQgBgAZaID3eKOQYCsel+icaWhtgDXfndZna5wAIM333wLMAGz2cz/BobABIgAAbsGgaBURxckIQkmpOygSfh8/vZ87rIAGAL6oRqu5gBAHTR6PC+KzzUBb77zi18aBFy7do0dj3fL5AIlQOn/LibANCmQ+ps2Bu+l6gs1eE3BaQH7SnUY7ut1gKyw/4YAVT9aYiur0xXKIXD9Oh4CMyFvgfzeFMiKr59JgNL/6o133QQk5IK8kiT7CQph4P3Fwj0HwL5kQOqPCSj+NQQUkyAi4KYqffNmfeGgnAQPiDqoACeAvaIhCAEf4PWJyfSq/J67CKANwocFUIOHh4egTZRZQLY/HMpveggUspuAwxLVhWQM74zHt2CM3xFCQ0he+FXxhfUdUAIGhAAwLGCi9fcQ0FT3UQFicoOGAGoB2X6B+hYxGdQcOwRjTI7HzVNgXLc/dloAJyA0BHB6OQfmTeaGgMxsr6mu9APgDeEAsQD62MtY/ZPyHuAqMv3oBq5wYNL7uBA/Fo4LlICCgVysD1k2LdDC12Mcmq5LODu0Wq6h2F2r/hERERERPcft2/70FLzr2gC2o48EmQ537xSPqTu1WAXbTYw9qeRJU7Z0TXZXloX4NelP7n2uyWhrTi7JxzbWP8s0AyPlRR6Nh9oP2ZFdnuw0jpyVikxfv1O54jUDsrAC2WkyPZuxcgVXlsv70WiQK2cubZ7tqeJ2gu/pXYC7RH/luC20/so3b6JfejqcOWYCfiO/9nCHMnmfM5Tf2BuksYX4rTgWv8Px7VgKY0MWpvz24G0kq/5Pp64OQuXsV3JtcMjiZGenae251isWTXTFCShXBxAB927ef3DjJlo2yqR9Z7g/XgJ+D3+QX3/ECirXn8g4+JCx8QClT80OVs58am/vdi2ieWAEe1PJQSnsVM56tuMioJoFkAXswZ/gtu6Q1B8t2YUt4M/iE/EXvaR0SCzgkFjAobKAuZanRuwhR0A5STXxLWnv01L6tOlgEcxrAygC1AzpGybg3s0PPpRfdv0rTx0TkEKx6lTLf4XP5Nfn6MSEMcYL+S0io/Ri/Ep86CCgju5So0PEfgSGOcvDYCgWRrxICMgIw0T/5kSESQCSH35ybXTtb48qeb+ubnc1eWrePcGGQCVj8e5dLSvbb9Y7rQQIAnlBrQ+6j9CQRe47VYf1U0AdMRKuIaGGO6nOLwuiPw/gU6y/uP+FnP4mX9xvCJDjP/WUZ4pO2CRqLrKyRX7iB9BlbyLbPgHGJ0+p/vQxKMpDXTq52BG4mjflgdVgYCzOIfIWAb7hA0VEREREbAFDvDCtXDk4ZHke61/P+GhhsRXhffpBlx6ksJTfl/jRfATI1XwXvvzyq6/gEerOntK/gPzl1g24dw9u3KrTy9gNc1liSGR6oQneqN80htFw+MRgwP/hYiFMZV1jFG2CZGBJvfGF9rz+rvAP7Youh7KCKQtumnQjNmUvWVfBq84jXcdMBjt6c7BM0MGVcoyX8MRyWvZnEqBcLVRC6V78Nw1AE/D1N48ff/O17s9QQD7V7honoIxG6p2mYjEKHXhIRblUkWpfO1PrMYiAB2qvDje4VKy7CKDhJVeXpJe7e9qiloWs9U/N/FDY+m5T/KlMGiF3FQbkQIZZvtgHRRlABZ4ynhPYAiYTfF59fHKiwktNgNRfoCUwyjgNFuwiMfGm/7UNIP3LO1jPAZ/BrgQ8bTLkuVEe5n4CDuSvB+pfnawMbAgLZAEken3wYP/BCRw1FT5RvRutjwBqAd8W8jNTf63geFlgYRbXhEH63nw+Nwio7mz5Y7FYvP9wsXhIDjwsnXPAyYkaAHgSfDIcjtY4CZI54NtqDqgYUPrnRjh6S/V3oYsv9+AIMaAqOkDTXgYmAR99VP0jBuKcA4bZyckJnGAG6GNw3U+BZ+IZjv9p6LacTPSClZwB5b9UMwDGj/rX3foCfQwqiyjhmANgqIAJsN3DLgQQpMW9f1b7AZYzguYMK63lSapmysd16j//9W/zY11EMWtU0iBTS3pZfWCjvR+wfRw8f36AxOme4ip93DBGO2w8BiMiIiI6Y4hPR7/4Tk0x373Ydqc2iJcALxvh+3rW/X7b3doYrit1r1fCi/KJo75rG5jBDBf4j8WZEes7eTYr+J91r2hVvFQBVG0CrzQBr5ocxG2w+RG5poRtPdALVIaZeqbPvPWfIa6XCl9HjVPXg/UnpRdybRTl5i1SkF6YwuvBa3N3ljW3SQLkDKBC6JdG42YfJnhjrNRfby/mpv62o7vTdIr1ey2/vTYyzLZIQF7f79xNQE6GPMBxitOw/jYCUsNkioPmAyOcNgjIYDabbc7T1Qq7CeBlkP5Sd2NS7GwBm50ECwMoX5opdHiuCXiOMuX+CnB65zlgs9EanfTua/E+zkQKEQYMfjo/BYTY4BQ40wqXPTitxVOsI50DsJSv//T5VoP1H9SyLDz9YZt96NNqRURERERExBkjB5941oARcWRWekOiC3Z2qP7gEc+eACAUGAQUaSnOkI9S9c3IoELmWp6UmdzhbU5855wlQ7FDtkECTApMAsq0ps/F7ZHq0QwGATidE0CDRb4YYB7G3QgB+DAwJaBY/qg6WfwY4T5XGTABI4tOYY0NcZ1/P2AlAjZoASsRsGEL2OwcQLH1OWDDTwG+3rHlp0APsF0/ICIiIiLicsP/HtlFR/pfAT8+RGc3pZdydIk+J1e9Rwo/5uh9hnH+1PICRe2b0M8/aCv3Dkv4nyRAoNPJipURY4C+WarP67eT+4YUjoX4MRfH+G3r5UJGtOb7tVqRwXwg/zXHt2FunmdXMpjyQH0NeureZtW5+SN9h8ZTUKft9xwEFB+NluzXn68HCSSJulDL++pLf/6eSpdXkv2eElBYgMQxvuNqXlgap5MRAY9KNCbeUu4dRsUzcIrOvMhgdAiLoYOACzcJjgGOj47xtF8uR+iQFNb8Fy77hvFLeX9ensu35iMiIiIiOoO+HxCS6SGqtnLb9rrKIdD3A0IyPUbXVm7bXlc5eP+hwYtVZHqQsq3ctr2uchD0/YBXuoJaPlW+4Wkll0dpi/TnjQxUFs70Vzr9lbN9Ad50daKTpAvaf4Hfd/ABdAPQyHUlotoNPj3Fu8Oh/Dyd5ddb5LZ0vHtm/wlGf8RPP/0kzP4IcbLi/hqgd3odshq9p6TDuEMsv2AK+fMTAoL9EfV/h3xS6r8+AqboM+gsBNh+tlEo2L7FQnwWcCJK/VcmIDwE1KdvtTHx0BCBEIHeISVIfipLBk6a/EHQ9wMsk1o9CepJjE5SQGX3pGqdJGn7dJI102t+XLIaA40cxKYfY10fo23lMDbtyHR1pNrKYWzale3qSreVIyIiIiIiIjyoHIczk3sP8vcDw/IFJAD8BBRfWEHhJ0DQP3rYb5QfSQgemRAE9TeXTP78Xd8RLeDSzwGX/SkQERERERERsW4k58cTCJ6ChKz9QdeE/H2gPiMRgb6uQAC93+dJ/3VYANX3XOlvWkBxvL34chDQ7L2Z+hocqtIXdg7Iapj64zte6n9+bKCrBZT5z6/+XS3g3Ovf9Sng0P/CzgEBaP3Pjw0ELaANlN71/4iInuP/VPKCJpghgS4AAAAldEVYdGRhdGU6Y3JlYXRlADIwMTYtMDktMTRUMTM6MzI6MzktMDQ6MDB6ohKoAAAAJXRFWHRkYXRlOm1vZGlmeQAyMDE1LTA2LTAxVDEwOjM3OjIxLTA0OjAwKEFuvAAAABl0RVh0U29mdHdhcmUAQWRvYmUgSW1hZ2VSZWFkeXHJZTwAAAAASUVORK5CYII=)}.ui-button .ui-icon{background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAQAAAADwCAQAAABFnnJAAAAABGdBTUEAALGPC/xhBQAAACBjSFJNAAB6JgAAgIQAAPoAAACA6AAAdTAAAOpgAAA6mAAAF3CculE8AAAAAmJLR0QAiEnuKCAAAAAHdElNRQffBgEKJRWQ+SdFAAAaqklEQVR42u2de5BlRX3HPwdIKGJYiCGwwrJbUolgopidgUr5SJWUIXeSqk3UYsndsaJGyQ7RqGiZnZHM8Aez4tzRAAuS2qXAWFTNI7tEDVSFOyJiYdxScXd9hrwEB4m7+keM6x8pYsnJH+fVfU6/zjn3zr1zT3+n7txzz6+7T3f/fv04/fv1r4MFPJqMMwadAY/BwgtAw+EFQEabkPagM7GR8AIgos0KsNIkEei1AAy+/bQJK8dcAfagE4Ek5cGXsYeQBcDcAYbpnwm29qOPH8ZPb2vD2J6dMLFaCSL2r8YiYEp5hPoIUQB60QHuqZFCEjdph+VRJy4EBKwCqwQEhpTrlHHoEKTrAEkRk3agQwiF6hERpRNUip+0Mt3zbc8Oa+bdNWVbGTcRsh7A3AG6wtQG7cNH9HQTC82p1GubpiFITLlePzNkCEqvBJpbkakNZpVate3YUzC3TXPezX1glrKtn9lUOKt0DBvz9FVTv8u0p7CKqf8KHOLqhkAx5ZFhf5UeYLTRZmWU2GuHF4CGw68ENhxeABoOLwANhxeAhsMLQMPhBaDh8ALQcHh7gHzcQed/g1HGHsDNIsCmjGkb7QHMT7Czp449gF0dHuV9pISknD2AmwbMXIV6Bu3RXLumbWO/LfWV3Lc+9ZGxBijaA0TQr4YnoUz6Nj3dFtvFHsCUO/PT7fHNCOO0k++RgGwPoLqWserUC6jD2Nuniz2Aqf255U0vPqHV2qDMkzYFqiiD2qwY29gw2wOYhMvW/yQlD0dJX9hrbeDgK8ckni5xB53/DYZXBzccfiGo4fAC0HB4AWg4vAA0HF4AGg4vAA2HF4CGo/zGkFFHOMBV/vprpaXzf1a96H2phEHmILTmoLoqyB5zACWXh4AQjLp+F/8AYQVKWVR9hi3/EesDYyp24aga260ELqFKxD1DCmArfuBQAH38wKGCXIoQGpQ9LvkLDDT5u9wzEoq9BswlNAtQaIkNtkYs5V8cAlyLr7PWsVdS0IMOPjRqIm2jaJ0chGnsQEkVn656StK89HkIDXRz2lnpzM1AzGUAZSeBoUPrsYVykc5qbdyNuYFD6iYGuaRbtQZMTdAlbXsdFOhlXgOzLs4llJpm7gLtEmxOw9bFunXRthZke7rLJLIq7CJup0s5KNMDuHWd9Wa5gWMv0688BsYO1i3dwCFMVZiHafMAqIx7libQ4DDoHGzm51eI61cCGw4vAA2HF4CGwwtAw+EFoOHwAtBweAFoOOTNoYmz1MHB7g+8n3CpAReNaLV4tr3Rrk8phUwAko1RLu7eq1VA71AtLVvO3WrA5Go208a1S8eO9JTJn74M7co1EOZyCag3h5q3cLpotNuKe70TAV1abq4h9Pl3qwHdM9q57bXtUrGzEth6oHpb0wsbdOWtYS7u1G1bsHUbRN0saew50KVjd+Fuz7mbQ3q1xqDI2iBHt20sbxt9EYdSymaFsU5hHRTDlBUA9woISsR1y4G5Cl2eb9/br3++LbZNAOx1YGagXQDaFmfWSgEo9xaQVUAVlUUgpKFOPZS+Tc+vgizfVecQpqfvianJCK72IGB6fhJTPQewpZz5bjDtb87nsqQ9gKkC5AmMqfjmzJmKaEpDLJrd7EvFArsAmkqwmnMg0S+n+Sb2rqbH3rjlkrJDgJs5VWh1EWEeBevEdqtedTncxuD6Jm2mdKofamOfAyjh/QOIMAvgSMILQMPhl4IbDi8ADYcXgIbDC0DD4QWg4fAC0GsMUp1dAXl7ABtM+iqXordr6rv7jfq5CyyL3UNW9qI9gAkmjbnLKmGisdvjsMFUj7qbq8zbwwPr9lc7g3XxTakPCNlCkJgtu7ff4mKjuDWy2unfrgvNYNLY2WIH2nDiXZ2207R5NHSiupd0Q6CeA+iMDsz6qmxoqGK0ELUcu9mU3odBiKuuLyhxV/Vc1fPtO5uHEpkAyIrC8gfIRwesJ+wrHz8g0+VV20CdhanrgqLac91C1PHx0QdkAiAqCqvIsO0kAbuyte7oGAg9iLqHkL9VIXrTilVPkHuPoeknxCFgNc2UqgOPOvjI3EuNVaM9gIu23+4ewozMFkBtUmGu+mwQ0nsXSUIGJaliiKoGNX2BWhuom8aAi7JUNwnshbLVzWqx6kTTZRKJIQeb8DAZrw6WMTRd80bBrwTKaBj7vQA0Hl4AGg4vAA2HF4CGwwtAwzF8AtAalkXSZiAvAG66bJPKJnSi6kK06G7Iq9ig/SAMDcq5i3dTxUzUyE+XREhaxnBVXdZnGKETwOtAFgDzKrV5tTtp1S26ShEI04VS9d69qOufSEN0NfGTq2pO1cXep7zGcgSRCYDs7r2ITB+uc5keEMTsX1M+y9y1R13/GhOGvbPJ09XPly0K8qm4uY9oHBJfwVmVmT1e2zRZCfurj+NrTq6c1bv/9U7VE2O2jD5CR8DXQSIASdWaTKZAPDRBjfpHouj6D/np+TzIByEUc7giPTugYVtA9ci8hYtVpncwYj/1wvVYCR09EoGwMI9IFMFqr/xyfnrlVr4BKPMWkFWxzibPdiSTiT6RUrtAUOgHAuHpqoHIbE8ku4/wSCGfF2A7cMRkdln3JIu1NG2X18jA8V6CVfysX4n8QpCp85bbYH/akXkOUAervuWrMGwnh3ombTCGTxfgsaHwAtBweAFoOLwANByjJACz6UrDbF/Sv4yx+O+yQRe1d4gE4GBccescrJzSYxZNvw0hT0rWAmWZOMt8ej2vjD1bSzwu42mu5RjHuJanlSIwa8393pi6V/MMPd0WE+7L/ZmfkHIp2hgS8jBPAecxJQTOXskOpvcPcaMm6WyR6Ai7DTuLiqlHWOIpgYWwzFukyp3PhZ9jfwm6nENV7vZySPo9xb3S7zGuZYFx4BgzPMpxbQ2on+HiTFp/8qftUOwoRFbztjKmS36JACwC8Hkp+JqQeFFAnmWHpnqPgFIEQsbT62OKIn6Nq4TfsgBEmoDJlJbfIhYyJ4nAHPNaDwa6jW/j0u98Dsc4xjjbgFfwYcY1AnASgJdU3GEUkixpB84UMYRZAPIiHkC2EJSwvpsPEOMp4AQ/5tOG7I/F37u1IbYYYi/zlCQAeRwSChVySOqrAPZDKgJz7M/1CFkF6ityC4+n19co87CNiwh4kSGXf2mgmXtAszo+UKRSTsQS9n+MD4q3s5XAriWBE/y4EEbOwgWxLi9U2PNE+FVD+pN8zfj8J8iU1Yd4oiAAmQgUO/8Irdx3MXfXGXM6wz9yF/BeZpTxTwHPCNdFzDGffjYWCfvv5xxZBFyXglXsz+PFAJzBC9oQ5wNoJii2HiARATjEE9owAWgneVfnvvPYwifiq3coqJfQARaAGTrsKgwBeU1q1W2mdi8JthCf5O2FexH7j3AO8G6AeNAvoQsosj9fwPOtafxSejVeoNl6ALgsZvwTXMbTCvosT3MQeIJZTR9gxi/z3vQqjzY7eIi9zABnEjLDiwwGJXPsVzJph/DRYQwbbCHephCAKQ4BuzkSz6MWmY4I1ZVBRfl+kTXOXfH3uIJm6wEipkcioHoNm5Xoql5gW+5bVUUwQ9TO5SFmBwsgvBcsaIaBCPM1uvhjNUOobTruhVgEQGC/SQDmhOtip1Nk/+f5mPSrCHOXaO4B5hSveWXokAxR2Xe+iu4FQn6B+cIrYCQS+TudXOlskzy4QfgUsZy+5cByxRB6JCIgsX+YHETMAi8Xfj9VqRuvixAU7O9l6hEGo/beyyGZ/cMkAB4DwSjpAjwqwAtAw+EFoOHwAtBweAEYLTwu6DOcIAtAy2Fjth4uJ2+6YVapUZ8TdNnFt/yDhNJf3rLhcI5+WPFcUVu+tw90gC9Y6qeTW18og9fHf2YsscRS8kN8DWzRZQ6YV9jmr/OmeAXqMR7lpUwp1bnPsBs4wku5KqesBfd330S3L4ef49b4bpTaLQp935H01+5CfFd9fLTCt9AXehImAJYkdTdAh31M0AUm6Obf12nRBY5wPYfZDcr9E99nG/AclxpqdyleTFrm89wvCkDE/kibVhSBkD25nTVlTw+P9hN+ijfzKd7Mw+zSVNAs+znIVEGnJ279VD3B5fj2/+ISfshFPMc2jY+DGTqEBEyzoKUDBvpXOM0WfkdJT6p/GZgsWYMJ9UiqbhfphwtK+CNcr3j+QaZY5gG6ib2FqA5OllPnmavkqEXc0qXWHN7K91jnBCc5xg+UIWaZZxs38lwf1gGf4WK+y4V8l0v4njZUtJY+Y6Qj69QlnOa4Vl2TtL5JJXVCqjXdBjm1tcWvOdwB+APgXN4KQIu1TACelFbT55njSa3aVIc1bM6cb+FhdvFZfp8v8HqFcdks8xxiqi/sh5fyL/wm/8Fv8E3erlCpvAdIjKWmFfETOmCgb2FMY/iyJDE+v5bfYV+afrRFdlH5FDWu4Z95rfD7SwqTlncC24FdCPZWiQBcTWJMEX3v7wsLbuV7/Ddf5iRfZr1ATdg/Z3x2aNCHT6TuaVQ90Hd4Od/m1/k2v5VNglK0uYtE3z+tUP5k9DP5uYGezQFkZGNvhC+WrLuJXJnyPcTrpFp5nfb5uQYqTgKT1qu2SRtnLzfyzticoyidoRS3OMIWzTaDAt3Efvm8omIeQzIBWFPS38mHmOF2PsBH+FvukOiTBZGQVUJ16Rn781O/DK3cELBmoOuozxGpu/P0JSbjsT9ny+kuAG5e+lskQ0HZOUTEYH3rT94CEqjeAiZSFzVqAZFRfE/5IH9jzF0dekBoZL99Gp2JgOoN4HZu4kGuBw5zHXfyAYm6xCQP81Mm83HzTqKyd/myOEJISJcuYWwZrC+iLnVT5z/PLcKvWwr9yRRRx9+NyzCloJt+wx4t++rTl63sj4y0oo59gtRkS8IaE6DZQP8zPhHP+6/nE/xMEWIXkyzn47qqg6drLE94lEEHSkz+3BENUQUR9PYADYfXBTQcXgAaDi8ADYcXgIajeQIQqY1V7zSdVJX7Hod0zlXeHbrj4W0QBWA6rYDqryHV/QPURYsw3a51XGvV8Ln4/X9fQQQ+yj7u5V7exbu4i5sKMaPaeSj+dS5wbvwX4WY+Tsit3ErIx7m5EN/sviJvzZC3ZyjSbSGKnh5keozsNXCaBZ7lEeDtnJ2qPYuJ2E7Zhn5ZvS8xyQwdpllQLKpETz7BGMfZqclFsiB7A/dRXCl8dXp9mu8o1kJP8FWmmKETpyMvh9vV4cnqfVepSDavvarcZ3ZzIYLUUGZe4fIzZEKIkaqzM3XwQrxKfJyzeb6w72UYMAkscCWTwGRBAE6wE9iZsv+EIoWL4m/19tSn+UV+ApzH/ynpX+VGpnhxqtMv309eHa9fhqhWPWeZT3cVqprQGg8JVhTFHi4SwSuF6yL+lJ8D8P3khjgEPAIcZycn+GTporkfKWOKreykUkR6tknhWsRYzPKE/UWdfIs3GPPwv/wEgJ/wRgX1KFOEQDtmf3FZd1z4U2Necx3lfx6YZ4xxxpUWBS12AQeJFLtFmN19B3SZYRs7uJRLM5sheW9gxP4xpaegMHdVTdljyqINnbj1w7KyfxoTWr+K/V3J5iG/1v4dTguOcI4W4r+WDrCP7eh0els4XbpMGS5Jvx8C/kgR4q+ASIcxRaT3kxGSiVWx+cwCPwB+zpls4zYei25nc4CQ5zk7rrp1tlcw+cIYws3gyfQEUUuvmqN8I+7+oGgXJ7NfxcBp/kT4dQ/3G56uErDINUY0eJxWusCZkEbt/Bh/g3Q/5P7CHEBUFp/gQ6XnADdDbIWxlNVuNgTMcDbP81UOss52RRebOYhWu4q2OZMOcn9mquoJCzHzsmsRCfujgWBbNsoBmcHbIhMEyvbb4UF2xn9F9sMCJ3gYeIxoplHEGp/lC5zL2UpzrDmLg43zOZ/7OJ9fif+bsVNxL5kDXIm6Qe3gTHawgx3AzUmIbAiI/F9EneDMEE4Bo83RM3T4JguKzdER+59jLLaNzXsBiNhvmrjdxnX8J3Cxgv0AjzJNyDE+SpedWsu/hzWp7xecRuwt7D8+FG+uz/4fyoXYlttUXvRyIFpKqa2mFJ4RymoDB/kaaEaLbtrxf59tOa25et6tzr06/9H84nn+mLXYMGMLP83FXeXfeYpVbS2FBOl+gUMFL2R/yHxskjfHP+X6mIMK+wXZZV8+RNGhn9J/gVcHi9jFXwMf1rTiJc7lnlisWhzlNQURE6ESANEszi6OGwIvAA1H83QBHhK8ADQcXgAajrwAHNT6C7+br6eLtF/n7kFn3KM3kJeC/5XLgddzRSHcp6X18VfxKrbxpkFn3qM+xB7gAJcDcDkHcqHuTtmfrdC9UdkLnCSMPWar8D9xD2JfZhrGhaiTgqLqZP3khgOiALSACSYoqhpfo4yrurs1/qhxXvy9z5KrjsJgA5biyl/SxrOFsNFDTqbmGkUWv0RzvamRCUDU/tdYo9gHZIueoprW7tU2j4DA4VzQaJ9sXgSyzY2TGgbaQiwxyQHGOaBNAbYyHwuJXoxHCpkAtOL/LeFXEbYTQ4+AZltY8pQu8KyC0km/o/4hv24/qbmW7y4zEbtfUNEPcBPHuYkDmhRA5+h9ZJEIQCce/7uxzuryiqPwM2Q+81XoAj9S+M9JOn0d+13xAGs8YKDK3xlcTFhmgVOc4hT06ViqASBZChbVIEWViOzjto7H22gPb35zY8Z2PfvtrphDYJkHeCuTyhAhB2Jjzzt5nzaFU2nnnw9xUhgWTo3KLCDqAbLW3hI6/+zuV5RxVXc7ljl+oDgYHqZj+xxT61/WXMt3J+mmXniK9PdxJ2PcyfsMvra3OlFGZoaQHBqlocbft/N+BfWO3B70LCV9z6BXJ9s7f7uTBVsIGz3kFPfEWrqTmjZe9SSQIUUkACeVEi12cyu0c9RV9ijidNhnHL9N9gS2uMOBkRQAFyzwu+mb/1G+aDwxY5TRWAHwGEl4bWDD4QWg4fAC0HB4AWg4vAA0HF4A8uhYvPlvMgcQNogCELJuUQH17kiIQeFJnjTSO0ZbhY7VkmHTQe4BtrPPKgRqZMLT0qbQYT3WNHRYL4iQLH6HFfTDUkoqEdRvLU/iXcVVhvK5s9/FqmlTIO8rOMKzrCqXZPXehEMpXkh+TT+qvADo0GZ79GxDCofZXaBHRyDo4ssl0J/WoaPKzqjt1BFZEVQLAKhPnLAJABD7GZGVQtmv9Zh5WFLQCYA+vpxGL1isp4aK7debFOpJ4LMsKg8cseFZFlP2LwoVFLAY393BotIeKJ+CDrb4G4ORYH2EogBELCivk0vitVhnsXDmxjQBi6zTYlrLRLcnT1cWApPvgYi6aIwrUkND2E0FeQjQjf1ZCP2JAsMPcycfIZurlKduSogbQ+wFC5xDDiNccj2NyWjdTN2U8OrghsOvBDYcXgAaDi8ADYcXgIbDC0DDkRcA095bjxGEuDn0MwBcyDs0W0MjPdvntBtHPTYhEgFo0U3dj15OV8nkGRY5yhvoOiwU5xWyh3OewA9vMN1Dg2Qh6Dg7+TKvJuRzXEuodIccocW9bLc6ky26Ks7/lh0l9pvuoUEkAC26/IiLgEc5zjQ/5ELFHt4QOME93M862zUHmEbhVL6qx2N36ls4zZaCP+2Qa3icawSH62r646kvfhV9nGPxB4W/bg8FIl3A1cC3ALgWgG/xBq4uMHiGK5nkPmAvXd6tFQA1rgAuBmArZyj2IkbOZbZyBvCC4u3k4vhzBfCCIv2twMti+sv8240rIgF4EnilcPeV8T0ZHeAButzCDk6wS5me3kziQunXHbFn+wxbeb8gFkX6hbw//pjiR2G2KugeSiRzgHW2p5uml5jMnzIPJErgg0xxA1czpfWHrRoCDrNb+p23N+o33UODRACi8zB+xLd4JReiPjEgswZYBPYpz7kKR8tgavQhHhv3Z7GfoH/j70bF5tXDBm8P0HD42XLD4QWg4fAC0HB4AWg4MgGwnQdQl77Al1L6lxTn/vWb3u/yDZpeEclbwKcL5+V+RjoPoC7d5mau3/R+l2/Q9Mo48/cA7uatBcoVXMAj8XVd+u38eYH+Cs5LtQn9pve7fIOm10A0BGSe/8VtU69RXInI01fTo2VXtfEDQ3xb+vkU+hHfVn5b/s3xT0kb03TxTXQxF+pSl0TeVazaGbTNlWy2+3cF2IN6d3Dd9F3i29NXucN2jR+g3mAWlvgdCqkU6ZGr/d3a+kvufojb6MkOLdXWsHwx83Q09DAed4vjcT6dUHPfnL69wEkPZIsdaEXOJXVd/lzSDzF7FrjOmIObuU1gf09wVv0kBLwg/C+P0NojmNEbBusbgD3/9rg2NdmDBtrNfISP0FP2934IWALeQvUhoH4Xr89fMYVqXbgpfVP+iucvlKNHIiCyvwdDQDQJtJ0H4EZfASaZjK9EungSdqi4e1yg2ugY6Sjpcv7Dwt2vSBQbvWr9JOULK9Nvk9ivfmpJRAJwVMpAgqOKKxF5ejutwLY2fmiIb0s/n0I/4tvKb8u/KX7eeVVZOiB1/upSl0S0DrDGFbwiR1kVTvapS3+E3y4cRvkZ3rZh9H6Xb9D0GogEAP6BcziDS+O7R1nmL6Rwdel/zwWcndr8fYMHBfZsBL3f5Rs0vTK8QUjD4bWBDYcXgIbDC0DD4QWg4fAC0HB4AWg4RGWQ7XTeYad7VICsDRxPr44pQ9elewwdikNAPdYds6ZQr+UGtVPwkJAXABsDj3HMSE/cM+hgY6DOl3eCsKKu30ODvACMg5GB44wb6ZGHDj1CzAYTpgNfwG5Q4VESxSFgvEIqcmxzCvXar02APEpCf2TM8M3y/VtAH1DmvIBhp3tUgF8Iaji8ADQcXgAaDi8ADYcXgIbDC0DDsXkFoO0XhHoBWQDqr7OFzBIy2/d8t1mRHEB4VIQsAHviz6Bha90R+1cHnc1RgCwAKyT7+gYJW+v27O8hXHuAkHbhUw5h4U+NiL16MUzY7+cAPYFsEbTCKivKthUAq7lPObi5b0/Yv8dIX/VzgF5BFgBTD7AnZU3yKScE84U7xSNd2kL6qtRl9vtBoAcYph5AZH+gpXv29xSuPUB92I9wKsf+tiacRykM01tAwGr8KULFfj8H6AHk7eFtVmkPZecaxp1+/tujJrx/gIZj8+oCPHqC/wc2957uSJx+mQAAACV0RVh0ZGF0ZTpjcmVhdGUAMjAxNi0wOS0xNFQxMzozMjozOS0wNDowMHqiEqgAAAAldEVYdGRhdGU6bW9kaWZ5ADIwMTUtMDYtMDFUMTA6Mzc6MjEtMDQ6MDAoQW68AAAAGXRFWHRTb2Z0d2FyZQBBZG9iZSBJbWFnZVJlYWR5ccllPAAAAABJRU5ErkJggg==)}.ui-icon-blank{background-position:16px 16px}.ui-icon-caret-1-n{background-position:0 0}.ui-icon-caret-1-ne{background-position:-16px 0}.ui-icon-caret-1-e{background-position:-32px 0}.ui-icon-caret-1-se{background-position:-48px 0}.ui-icon-caret-1-s{background-position:-65px 0}.ui-icon-caret-1-sw{background-position:-80px 0}.ui-icon-caret-1-w{background-position:-96px 0}.ui-icon-caret-1-nw{background-position:-112px 0}.ui-icon-caret-2-n-s{background-position:-128px 0}.ui-icon-caret-2-e-w{background-position:-144px 0}.ui-icon-triangle-1-n{background-position:0 -16px}.ui-icon-triangle-1-ne{background-position:-16px -16px}.ui-icon-triangle-1-e{background-position:-32px -16px}.ui-icon-triangle-1-se{background-position:-48px -16px}.ui-icon-triangle-1-s{background-position:-65px -16px}.ui-icon-triangle-1-sw{background-position:-80px -16px}.ui-icon-triangle-1-w{background-position:-96px -16px}.ui-icon-triangle-1-nw{background-position:-112px -16px}.ui-icon-triangle-2-n-s{background-position:-128px -16px}.ui-icon-triangle-2-e-w{background-position:-144px -16px}.ui-icon-arrow-1-n{background-position:0 -32px}.ui-icon-arrow-1-ne{background-position:-16px -32px}.ui-icon-arrow-1-e{background-position:-32px -32px}.ui-icon-arrow-1-se{background-position:-48px -32px}.ui-icon-arrow-1-s{background-position:-65px -32px}.ui-icon-arrow-1-sw{background-position:-80px -32px}.ui-icon-arrow-1-w{background-position:-96px -32px}.ui-icon-arrow-1-nw{background-position:-112px -32px}.ui-icon-arrow-2-n-s{background-position:-128px -32px}.ui-icon-arrow-2-ne-sw{background-position:-144px -32px}.ui-icon-arrow-2-e-w{background-position:-160px -32px}.ui-icon-arrow-2-se-nw{background-position:-176px -32px}.ui-icon-arrowstop-1-n{background-position:-192px -32px}.ui-icon-arrowstop-1-e{background-position:-208px -32px}.ui-icon-arrowstop-1-s{background-position:-224px -32px}.ui-icon-arrowstop-1-w{background-position:-240px -32px}.ui-icon-arrowthick-1-n{background-position:1px -48px}.ui-icon-arrowthick-1-ne{background-position:-16px -48px}.ui-icon-arrowthick-1-e{background-position:-32px -48px}.ui-icon-arrowthick-1-se{background-position:-48px -48px}.ui-icon-arrowthick-1-s{background-position:-64px -48px}.ui-icon-arrowthick-1-sw{background-position:-80px -48px}.ui-icon-arrowthick-1-w{background-position:-96px -48px}.ui-icon-arrowthick-1-nw{background-position:-112px -48px}.ui-icon-arrowthick-2-n-s{background-position:-128px -48px}.ui-icon-arrowthick-2-ne-sw{background-position:-144px -48px}.ui-icon-arrowthick-2-e-w{background-position:-160px -48px}.ui-icon-arrowthick-2-se-nw{background-position:-176px -48px}.ui-icon-arrowthickstop-1-n{background-position:-192px -48px}.ui-icon-arrowthickstop-1-e{background-position:-208px -48px}.ui-icon-arrowthickstop-1-s{background-position:-224px -48px}.ui-icon-arrowthickstop-1-w{background-position:-240px -48px}.ui-icon-arrowreturnthick-1-w{background-position:0 -64px}.ui-icon-arrowreturnthick-1-n{background-position:-16px -64px}.ui-icon-arrowreturnthick-1-e{background-position:-32px -64px}.ui-icon-arrowreturnthick-1-s{background-position:-48px -64px}.ui-icon-arrowreturn-1-w{background-position:-64px -64px}.ui-icon-arrowreturn-1-n{background-position:-80px -64px}.ui-icon-arrowreturn-1-e{background-position:-96px -64px}.ui-icon-arrowreturn-1-s{background-position:-112px -64px}.ui-icon-arrowrefresh-1-w{background-position:-128px -64px}.ui-icon-arrowrefresh-1-n{background-position:-144px -64px}.ui-icon-arrowrefresh-1-e{background-position:-160px -64px}.ui-icon-arrowrefresh-1-s{background-position:-176px -64px}.ui-icon-arrow-4{background-position:0 -80px}.ui-icon-arrow-4-diag{background-position:-16px -80px}.ui-icon-extlink{background-position:-32px -80px}.ui-icon-newwin{background-position:-48px -80px}.ui-icon-refresh{background-position:-64px -80px}.ui-icon-shuffle{background-position:-80px -80px}.ui-icon-transfer-e-w{background-position:-96px -80px}.ui-icon-transferthick-e-w{background-position:-112px -80px}.ui-icon-folder-collapsed{background-position:0 -96px}.ui-icon-folder-open{background-position:-16px -96px}.ui-icon-document{background-position:-32px -96px}.ui-icon-document-b{background-position:-48px -96px}.ui-icon-note{background-position:-64px -96px}.ui-icon-mail-closed{background-position:-80px -96px}.ui-icon-mail-open{background-position:-96px -96px}.ui-icon-suitcase{background-position:-112px -96px}.ui-icon-comment{background-position:-128px -96px}.ui-icon-person{background-position:-144px -96px}.ui-icon-print{background-position:-160px -96px}.ui-icon-trash{background-position:-176px -96px}.ui-icon-locked{background-position:-192px -96px}.ui-icon-unlocked{background-position:-208px -96px}.ui-icon-bookmark{background-position:-224px -96px}.ui-icon-tag{background-position:-240px -96px}.ui-icon-home{background-position:0 -112px}.ui-icon-flag{background-position:-16px -112px}.ui-icon-calendar{background-position:-32px -112px}.ui-icon-cart{background-position:-48px -112px}.ui-icon-pencil{background-position:-64px -112px}.ui-icon-clock{background-position:-80px -112px}.ui-icon-disk{background-position:-96px -112px}.ui-icon-calculator{background-position:-112px -112px}.ui-icon-zoomin{background-position:-128px -112px}.ui-icon-zoomout{background-position:-144px -112px}.ui-icon-search{background-position:-160px -112px}.ui-icon-wrench{background-position:-176px -112px}.ui-icon-gear{background-position:-192px -112px}.ui-icon-heart{background-position:-208px -112px}.ui-icon-star{background-position:-224px -112px}.ui-icon-link{background-position:-240px -112px}.ui-icon-cancel{background-position:0 -128px}.ui-icon-plus{background-position:-16px -128px}.ui-icon-plusthick{background-position:-32px -128px}.ui-icon-minus{background-position:-48px -128px}.ui-icon-minusthick{background-position:-64px -128px}.ui-icon-close{background-position:-80px -128px}.ui-icon-closethick{background-position:-96px -128px}.ui-icon-key{background-position:-112px -128px}.ui-icon-lightbulb{background-position:-128px -128px}.ui-icon-scissors{background-position:-144px -128px}.ui-icon-clipboard{background-position:-160px -128px}.ui-icon-copy{background-position:-176px -128px}.ui-icon-contact{background-position:-192px -128px}.ui-icon-image{background-position:-208px -128px}.ui-icon-video{background-position:-224px -128px}.ui-icon-script{background-position:-240px -128px}.ui-icon-alert{background-position:0 -144px}.ui-icon-info{background-position:-16px -144px}.ui-icon-notice{background-position:-32px -144px}.ui-icon-help{background-position:-48px -144px}.ui-icon-check{background-position:-64px -144px}.ui-icon-bullet{background-position:-80px -144px}.ui-icon-radio-on{background-position:-96px -144px}.ui-icon-radio-off{background-position:-112px -144px}.ui-icon-pin-w{background-position:-128px -144px}.ui-icon-pin-s{background-position:-144px -144px}.ui-icon-play{background-position:0 -160px}.ui-icon-pause{background-position:-16px -160px}.ui-icon-seek-next{background-position:-32px -160px}.ui-icon-seek-prev{background-position:-48px -160px}.ui-icon-seek-end{background-position:-64px -160px}.ui-icon-seek-first,.ui-icon-seek-start{background-position:-80px -160px}.ui-icon-stop{background-position:-96px -160px}.ui-icon-eject{background-position:-112px -160px}.ui-icon-volume-off{background-position:-128px -160px}.ui-icon-volume-on{background-position:-144px -160px}.ui-icon-power{background-position:0 -176px}.ui-icon-signal-diag{background-position:-16px -176px}.ui-icon-signal{background-position:-32px -176px}.ui-icon-battery-0{background-position:-48px -176px}.ui-icon-battery-1{background-position:-64px -176px}.ui-icon-battery-2{background-position:-80px -176px}.ui-icon-battery-3{background-position:-96px -176px}.ui-icon-circle-plus{background-position:0 -192px}.ui-icon-circle-minus{background-position:-16px -192px}.ui-icon-circle-close{background-position:-32px -192px}.ui-icon-circle-triangle-e{background-position:-48px -192px}.ui-icon-circle-triangle-s{background-position:-64px -192px}.ui-icon-circle-triangle-w{background-position:-80px -192px}.ui-icon-circle-triangle-n{background-position:-96px -192px}.ui-icon-circle-arrow-e{background-position:-112px -192px}.ui-icon-circle-arrow-s{background-position:-128px -192px}.ui-icon-circle-arrow-w{background-position:-144px -192px}.ui-icon-circle-arrow-n{background-position:-160px -192px}.ui-icon-circle-zoomin{background-position:-176px -192px}.ui-icon-circle-zoomout{background-position:-192px -192px}.ui-icon-circle-check{background-position:-208px -192px}.ui-icon-circlesmall-plus{background-position:0 -208px}.ui-icon-circlesmall-minus{background-position:-16px -208px}.ui-icon-circlesmall-close{background-position:-32px -208px}.ui-icon-squaresmall-plus{background-position:-48px -208px}.ui-icon-squaresmall-minus{background-position:-64px -208px}.ui-icon-squaresmall-close{background-position:-80px -208px}.ui-icon-grip-dotted-vertical{background-position:0 -224px}.ui-icon-grip-dotted-horizontal{background-position:-16px -224px}.ui-icon-grip-solid-vertical{background-position:-32px -224px}.ui-icon-grip-solid-horizontal{background-position:-48px -224px}.ui-icon-gripsmall-diagonal-se{background-position:-64px -224px}.ui-icon-grip-diagonal-se{background-position:-80px -224px}.ui-corner-all,.ui-corner-left,.ui-corner-tl,.ui-corner-top{border-top-left-radius:4px}.ui-corner-all,.ui-corner-right,.ui-corner-top,.ui-corner-tr{border-top-right-radius:4px}.ui-corner-all,.ui-corner-bl,.ui-corner-bottom,.ui-corner-left{border-bottom-left-radius:4px}.ui-corner-all,.ui-corner-bottom,.ui-corner-br,.ui-corner-right{border-bottom-right-radius:4px}.ui-widget-overlay{background:#aaa;opacity:.3;filter:Alpha(Opacity=30)}.ui-widget-shadow{-webkit-box-shadow:-8px -8px 8px #aaa;box-shadow:-8px -8px 8px #aaa}/*!
+ul.dropdown-menu li.checkbox input{margin-left:3px}ul.dropdown-menu li.checkbox span{margin-left:20px}.dropdown-menu>li{position:relative;-webkit-user-select:none;-moz-user-select:none;-ms-user-select:none;-o-user-select:none;user-select:none;cursor:pointer}.dropdown-menu .sub-menu{left:100%;position:absolute;top:0;display:none;margin-top:-1px;border-top-left-radius:0;border-bottom-left-radius:0;border-left-color:#fff;box-shadow:none}.left-caret:after,.right-caret:after{content:"";border-bottom:5px solid transparent;border-top:5px solid transparent;display:inline-block;height:0;vertical-align:middle;width:0;margin-left:5px}.right-caret:after{border-left:5px solid #ffaf46}.left-caret:after{border-right:5px solid #ffaf46}.dropdown-icon{margin-left:-12px;margin-right:5px;padding:0;background-repeat:no-repeat;background-size:100%;background-position:50% 50%;display:inline-block;vertical-align:middle;height:18px;width:18px}a.accelerated{position:relative}a.accelerated span.accell-spacer{color:#fff}a.accelerated span.accell-text{color:#888;position:absolute;right:10px}body,html{width:100%;height:100%;padding:0;margin:0;overflow:hidden}nav.navbar{margin-bottom:0}#content{width:100%;height:calc(100% - 55px);padding:0;background-color:#fff}.pane-container,.pane-wrapper{width:100%;height:100%;background-color:white: green}.splittable{background-color:#fff;width:100%;height:100%;padding:5px}div.tabbed{height:100%}div.tab-content{height:calc(100% - 40px)}div.tab-pane{position:relative;height:100%}span.glyphicon.xclose:hover{opacity:.8}span.glyphicon.xclose{margin-left:5px;opacity:.2}a.tab-new.compact>span{padding:6px 0}.nav>li>a.compact{padding:0 5px}span.tab-dirty{display:none;background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAADAAAAAqCAMAAADCkShIAAAAIGNIUk0AAHomAACAhAAA+gAAAIDoAAB1MAAA6mAAADqYAAAXcJy6UTwAAAAzUExURQAAAAICAQAAAAAAADAwHSkoFVtYJvj4wdHPi/37sKOfVvv3joJ+OfLsa6GaOfryVf////09bBAAAAAGdFJOUwD+LWbH9lfFP3wAAAABYktHRBCVsg0sAAAACXBIWXMAAAsTAAALEwEAmpwYAAAAB3RJTUUH4AkVDAQs7+kkfQAAAetJREFUSMeVVY3WqjAMc7B1XffT93/bm3aA+l1Q7FGBQ7I0WcHH47RCCMvjhwpe9/Fr+JEBLMV4nwCBmHO8LwFkzplvEyBAIGS62dSClUveJNZ7DUn2kltNBXdsVcqNaBdriA1tX77hYndcTIG/RwuByAysFzO277sA84RXENoXidUFeMJLrcX2e/kcETthwvH5HG3YHZfWGHCrj763SNm3jCehfyBMAWYxq8HQRFLpmuFT6tnbdltLduyXj+scoolv1NFN9dNxIWE3s9BcfvbvBOrpfGrdcdgILEAJoGlIP4/WHVPYHOAChgGl3lXPJOxFwaUdhAQL3WRSU9UT3+YuF9k82FWv1rydqf4/UqvnWHh6ADAKUdrEziQsUpsdw8fQrHU53IDwN9p9o2qVKEgT+N7piVelN9/Lc3SqIMxkBJVXwnhrCl2QC/TOJAYUnRkdhDeJNURrxIcNVmGW6K/Cm2937AJkX3RPXZ2QXgjPaPfZsXHbC3gdYwI3wnO/Xxx3o+hF7dGaKrJJNGyzMNcNvworNKiNNCg1nI20+14QEaNzkljTAEwHnKvBSVvCVRoDhDa2aGGg1WppjiRYU3BXAVWDYWFo2sEU1J9Wm67KdRrWawdHUNvsH5VOT2f523z/x7xZ6+M3xvr4B2dMHj70RasaAAAAAElFTkSuQmCC);padding:0;background-repeat:no-repeat;background-size:90% 60%;background-position:0 40%;vertical-align:middle;height:30px;width:21px}.nav>li>a.compact.data-dirty>span.tab-dirty{display:inline-block}a.tab-chat{display:none}a.tab-chat.chat-alert{position:relative;vertical-align:middle;display:inline-block;height:30px;width:22px}a.tab-chat .glyphicon,span.tab-chat-count{position:absolute;display:block;top:0;left:0;width:100%;height:100%;text-align:center;line-height:30px}a.tab-chat .glyphicon{font-size:140%;color:red}span.tab-chat-count{font-size:80%;font-weight:700;color:#fff;z-index:10}.tabbed-select:{width:100%}.tabbed-create{margin:2em 0 1em;text-align:center}label.tabbed-left{text-align:right;margin-right:.6em;white-space:nowrap;width:5em}label.tabbed-right{text-align:left;margin-left:.6em;white-space:nowrap;width:5em}.tabbed-profile>label{font-style:italic;font-weight:400;color:#888}.tab-icon{padding:0;background-repeat:no-repeat;background-size:70%;background-position:50% 40%;display:inline-block;vertical-align:middle;height:30px;width:30px}.tabbed-profile{width:100%;text-align:center}.tabbed-profile .select-profile{display:inline-block}form.search-sources{margin:3em auto 1em;width:80%}.CodeMirror{font-family:monospace;height:300px;color:#000}.CodeMirror-lines{padding:4px 0}.CodeMirror pre{padding:0 4px}.CodeMirror-gutter-filler,.CodeMirror-scrollbar-filler{background-color:#fff}.CodeMirror-gutters{border-right:1px solid #ddd;background-color:#f7f7f7;white-space:nowrap}.CodeMirror-linenumber{padding:0 3px 0 5px;min-width:20px;text-align:right;color:#999;white-space:nowrap}.CodeMirror-guttermarker{color:#000}.CodeMirror-guttermarker-subtle{color:#999}.CodeMirror-cursor{border-left:1px solid #000;border-right:none;width:0}.CodeMirror div.CodeMirror-secondarycursor{border-left:1px solid silver}.cm-fat-cursor .CodeMirror-cursor{width:auto;border:0!important;background:#7e7}.cm-fat-cursor div.CodeMirror-cursors{z-index:1}.cm-animate-fat-cursor{width:auto;border:0;-webkit-animation:blink 1.06s steps(1) infinite;-moz-animation:blink 1.06s steps(1) infinite;animation:blink 1.06s steps(1) infinite;background-color:#7e7}@-moz-keyframes blink{50%{background-color:transparent}}@-webkit-keyframes blink{50%{background-color:transparent}}@keyframes blink{50%{background-color:transparent}}.cm-tab{display:inline-block;text-decoration:inherit}.CodeMirror-rulers{position:absolute;left:0;right:0;top:-50px;bottom:-20px;overflow:hidden}.CodeMirror-ruler{border-left:1px solid #ccc;top:0;bottom:0;position:absolute}.cm-s-default .cm-header{color:#00f}.cm-s-default .cm-quote{color:#090}.cm-negative{color:#d44}.cm-positive{color:#292}.cm-header,.cm-strong{font-weight:700}.cm-em{font-style:italic}.cm-link{text-decoration:underline}.cm-strikethrough{text-decoration:line-through}.cm-s-default .cm-keyword{color:#708}.cm-s-default .cm-atom{color:#219}.cm-s-default .cm-number{color:#164}.cm-s-default .cm-def{color:#00f}.cm-s-default .cm-variable-2{color:#05a}.cm-s-default .cm-variable-3{color:#085}.cm-s-default .cm-comment{color:#a50}.cm-s-default .cm-string{color:#a11}.cm-s-default .cm-string-2{color:#f50}.cm-s-default .cm-meta{color:#555}.cm-s-default .cm-qualifier{color:#555}.cm-s-default .cm-builtin{color:#30a}.cm-s-default .cm-bracket{color:#997}.cm-s-default .cm-tag{color:#170}.cm-s-default .cm-attribute{color:#00c}.cm-s-default .cm-hr{color:#999}.cm-s-default .cm-link{color:#00c}.cm-s-default .cm-error{color:red}.cm-invalidchar{color:red}.CodeMirror-composing{border-bottom:2px solid}div.CodeMirror span.CodeMirror-matchingbracket{color:#0f0}div.CodeMirror span.CodeMirror-nonmatchingbracket{color:#f22}.CodeMirror-matchingtag{background:rgba(255,150,0,.3)}.CodeMirror-activeline-background{background:#e8f2ff}.CodeMirror{position:relative;overflow:hidden;background:#fff}.CodeMirror-scroll{overflow:scroll!important;margin-bottom:-30px;margin-right:-30px;padding-bottom:30px;height:100%;outline:0;position:relative}.CodeMirror-sizer{position:relative;border-right:30px solid transparent}.CodeMirror-gutter-filler,.CodeMirror-hscrollbar,.CodeMirror-scrollbar-filler,.CodeMirror-vscrollbar{position:absolute;z-index:6;display:none}.CodeMirror-vscrollbar{right:0;top:0;overflow-x:hidden;overflow-y:scroll}.CodeMirror-hscrollbar{bottom:0;left:0;overflow-y:hidden;overflow-x:scroll}.CodeMirror-scrollbar-filler{right:0;bottom:0}.CodeMirror-gutter-filler{left:0;bottom:0}.CodeMirror-gutters{position:absolute;left:0;top:0;min-height:100%;z-index:3}.CodeMirror-gutter{white-space:normal;height:100%;display:inline-block;vertical-align:top;margin-bottom:-30px}.CodeMirror-gutter-wrapper{position:absolute;z-index:4;background:0 0!important;border:none!important}.CodeMirror-gutter-background{position:absolute;top:0;bottom:0;z-index:4}.CodeMirror-gutter-elt{position:absolute;cursor:default;z-index:4}.CodeMirror-gutter-wrapper ::selection{background-color:transparent}.CodeMirror-gutter-wrapper ::-moz-selection{background-color:transparent}.CodeMirror-lines{cursor:text;min-height:1px}.CodeMirror pre{-moz-border-radius:0;-webkit-border-radius:0;border-radius:0;border-width:0;background:0 0;font-family:inherit;font-size:inherit;margin:0;white-space:pre;word-wrap:normal;line-height:inherit;color:inherit;z-index:2;position:relative;overflow:visible;-webkit-tap-highlight-color:transparent;-webkit-font-variant-ligatures:contextual;font-variant-ligatures:contextual}.CodeMirror-wrap pre{word-wrap:break-word;white-space:pre-wrap;word-break:normal}.CodeMirror-linebackground{position:absolute;left:0;right:0;top:0;bottom:0;z-index:0}.CodeMirror-linewidget{position:relative;z-index:2;overflow:auto}.CodeMirror-rtl pre{direction:rtl}.CodeMirror-code{outline:0}.CodeMirror-gutter,.CodeMirror-gutters,.CodeMirror-linenumber,.CodeMirror-scroll,.CodeMirror-sizer{-moz-box-sizing:content-box;box-sizing:content-box}.CodeMirror-measure{position:absolute;width:100%;height:0;overflow:hidden;visibility:hidden}.CodeMirror-cursor{position:absolute;pointer-events:none}.CodeMirror-measure pre{position:static}div.CodeMirror-cursors{visibility:hidden;position:relative;z-index:3}div.CodeMirror-dragcursors{visibility:visible}.CodeMirror-focused div.CodeMirror-cursors{visibility:visible}.CodeMirror-selected{background:#d9d9d9}.CodeMirror-focused .CodeMirror-selected{background:#d7d4f0}.CodeMirror-crosshair{cursor:crosshair}.CodeMirror-line::selection,.CodeMirror-line>span::selection,.CodeMirror-line>span>span::selection{background:#d7d4f0}.CodeMirror-line::-moz-selection,.CodeMirror-line>span::-moz-selection,.CodeMirror-line>span>span::-moz-selection{background:#d7d4f0}.cm-searching{background:#ffa;background:rgba(255,255,0,.4)}.cm-force-border{padding-right:.1px}@media print{.CodeMirror div.CodeMirror-cursors{visibility:hidden}}.cm-tab-wrap-hack:after{content:''}span.CodeMirror-selectedtext{background:0 0}.CodeMirror-hints{position:absolute;z-index:10;overflow:hidden;list-style:none;margin:0;padding:2px;-webkit-box-shadow:2px 3px 5px rgba(0,0,0,.2);-moz-box-shadow:2px 3px 5px rgba(0,0,0,.2);box-shadow:2px 3px 5px rgba(0,0,0,.2);border-radius:3px;border:1px solid silver;background:#fff;font-size:90%;font-family:monospace;max-height:20em;overflow-y:auto}.CodeMirror-hint{margin:0;padding:0 4px;border-radius:2px;white-space:pre;color:#000;cursor:pointer}li.CodeMirror-hint-active{background:#08f;color:#fff}.CodeMirror-dialog{position:absolute;left:0;right:0;background:inherit;z-index:15;padding:.1em .8em;overflow:hidden;color:inherit}.CodeMirror-dialog-top{border-bottom:1px solid #eee;top:0}.CodeMirror-dialog-bottom{border-top:1px solid #eee;bottom:0}.CodeMirror-dialog input{border:none;outline:0;background:0 0;width:20em;color:inherit;font-family:monospace}.CodeMirror-dialog button{font-size:70%}.cm-s-prolog span.cm-number{color:#000}.cm-s-prolog span.cm-neg-number{color:#000}.cm-s-prolog span.cm-atom{color:#762}.cm-s-prolog span.cm-uatom{color:#762}.cm-s-prolog span.cm-qatom{color:#008}.cm-s-prolog span.cm-string{color:#008;font-style:italic}.cm-s-prolog span.cm-string_terminal{color:#008;font-style:italic}.cm-s-prolog span.cm-bqstring{color:#040;font-style:italic}.cm-s-prolog span.cm-codes{color:#040;font-style:italic}.cm-s-prolog span.cm-chars{color:#040;font-style:italic}.cm-s-prolog span.cm-functor{color:#000;font-style:italic}.cm-s-prolog span.cm-tag{color:#000;font-weight:700}.cm-s-prolog span.cm-key{color:#000;font-weight:700}.cm-s-prolog span.cm-ext_quant{color:#000;font-weight:700}.cm-s-prolog span.cm-qq_content{color:#900}.cm-s-prolog span.cm-qq_close,.cm-s-prolog span.cm-qq_open,.cm-s-prolog span.cm-qq_sep{color:#00f;font-weight:700}.cm-s-prolog span.cm-qq_type{font-weight:700}.cm-s-prolog span.cm-comment{color:#060;font-style:italic;line-height:1em}.cm-s-prolog span.cm-comment_string{color:#060;font-style:italic;line-height:1em}.cm-s-prolog span.cm-var{color:#800}.cm-s-prolog span.cm-var-2{color:#888}.cm-s-prolog span.cm-anon{color:#800}.cm-s-prolog span.cm-singleton{color:#800;font-weight:700}.cm-s-prolog span.cm-identifier{font-weight:700}.cm-s-prolog span.cm-module{color:#549}.cm-s-prolog span.cm-head_exported{color:#00f;font-weight:700}.cm-s-prolog span.cm-head_unreferenced{color:red;font-weight:700}.cm-s-prolog span.cm-head_built_in{background:orange;font-weight:700}.cm-s-prolog span.cm-head_iso{background:orange;font-weight:700}.cm-s-prolog span.cm-head_hook{color:#00f;text-decoration:underline}.cm-s-prolog span.cm-head_extern{color:#00f;font-weight:700}.cm-s-prolog span.cm-head_public{color:#016300;font-weight:700}.cm-s-prolog span.cm-head_constraint{color:#008b8b;font-weight:700}.cm-s-prolog span.cm-head{font-weight:700}.cm-s-prolog span.cm-goal_built_in{color:#00f}.cm-s-prolog span.cm-goal_imported{color:#00f}.cm-s-prolog span.cm-goal_autoload{color:#008}.cm-s-prolog span.cm-goal_undefined{color:red}.cm-s-prolog span.cm-goal_dynamic{color:#f0f}.cm-s-prolog span.cm-goal_thread_local{color:#f0f;text-decoration:underline}.cm-s-prolog span.cm-goal_constraint{color:#008b8b}.cm-s-prolog span.cm-goal_recursion{text-decoration:underline}.cm-s-prolog span.cm-meta{color:#00f}.cm-s-prolog span.cm-op_type{color:#00f}.cm-s-prolog span.cm-file_no_depends{color:#00f;text-decoration:underline;background:#fcd}.cm-s-prolog span.cm-file{color:#00f;text-decoration:underline}.cm-s-prolog span.cm-nofile{color:red}.cm-s-prolog span.cm-option_name{color:#3434ba}.cm-s-prolog span.cm-no_option_name{color:red}.cm-s-prolog span.cm-flag_name{color:#00f}.cm-s-prolog span.cm-no_flag_name{color:red}.cm-s-prolog span.cm-error{border-bottom:2px dotted red}.cm-s-prolog span.cm-instantiation_error{border-bottom:2px dotted red}.cm-s-prolog span.cm-link{color:#762}.cm-s-prolog span.cm-expanded{color:#00f;text-decoration:underline}.cm-s-prolog span.cm-undefined_import{color:red}.cm-s-prolog span.cm-unused_import{color:#00f;background:pink}.cm-s-prolog span.cm-xpce_method{font-weight:700}.cm-s-prolog span.cm-xpce_class_built_in{color:#00f}.cm-s-prolog span.cm-xpce_class_lib{color:#00f;font-style:italic}.cm-s-prolog span.cm-xpce_class_user{color:#000;font-style:italic}.cm-s-prolog span.cm-xpce_class_undef{color:#000;font-style:italic}.cm-s-prolog span.cm-outofsync{border:1px dotted red}.cm-s-prolog span.cm-html{color:#909;font-weight:700}.cm-s-prolog span.cm-entity{color:#909}.cm-s-prolog span.cm-html_attribute{color:#909}.cm-s-prolog span.cm-sgml_attr_function{color:#00f}.cm-s-prolog span.cm-http_location_for_id{font-weight:700}.cm-s-prolog span.cm-http_no_location_for_id{color:red;font-weight:700}.cm-jumped{background:#ff0}.CodeMirror-hover-tooltip{background-color:#ffd;border:1px solid #888;border-radius:4px 4px 4px 4px;color:#000;font-size:10pt;overflow:hidden;padding:2px 5px;position:fixed;z-index:100;max-width:600px;opacity:0;transition:opacity .4s;-moz-transition:opacity .4s;-webkit-transition:opacity .4s;-o-transition:opacity .4s;-ms-transition:opacity .4s}.CodeMirror-hover-tooltip .pred-name{color:#00f;font-family:monospace;margin-right:5px}.CodeMirror-hover-tooltip .pred-tag{font-weight:700;margin-right:5px}.CodeMirror-hover-tooltip .pred-summary{font-style:italic}.CodeMirror-templates-variable{outline:solid #4664a5 1px}.CodeMirror-templates-variable-selected{background-color:#b4d7ff}.CodeMirror-hint-template{background:url(data:image/gif;base64,R0lGODlhEAAQANUAAH5weoJ1g4h8kY+EoZaMsZyTv6CYyGd9qWqArG+Fr3aLs3yRuIKXvYmdwY2hxIaUroiVrIyXqoidwZGlx4+aqJScpfr9//f8//b8//n9/9Xz/+v5/5ifovH7/+n5/+36//D7//T8/+r6/+v6//P8//f9//b9//r+//n+/56inqKlm6iol62rlP7xevzndvjQasiYQP///wAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAACH5BAEAADEALAAAAAAQABAAAAaEwJhwSCwOYcikEkmEtZ7QKKzpMhgKhIEgAHBNj6+wePwVsjTotJpFXGk88Hh8RVRpJo4GY6FIIDwqRCkaIxuFIoUjIylEHHd5e30IHxxEFRogIB2ZmpoVRBR3EgsJByGnJBREERolFyWwJhgmJRFEEBonFigoFhYZvRBED8TFxsRGyUVBADs=) no-repeat left center;padding-left:18px;margin:3px 0}.CodeMirror-hints-contextInfo{position:absolute;z-index:10;border:double #d4d0c8 3px;max-height:200px;max-width:400px;min-width:400px;overflow:auto;background:#ffffe1;font-family:Tahoma;font-size:12px;padding:5px}.CodeMirror-hints{overflow-x:visible}.CodeMirror-hint{position:relative;max-width:none;overflow:visible}.CodeMirror-hint-description{display:none}.CodeMirror-hint-description.active{display:block;position:absolute;z-index:20;left:10px;top:0}.CodeMirror,.prolog-editor{height:100%}.CodeMirror pre.CodeMirror-placeholder{color:#999}.CodeMirror .source-msg.error{color:red;border-left:2px solid red}.CodeMirror .source-msg{position:relative;border-left:2px solid #000;padding:0 5px;background-color:#ddd;cursor:hand;cursor:pointer}.CodeMirror .source-msg>span.glyphicon{color:#000;position:absolute;right:5px;top:5px}.CodeMirror .source-msg-charmark{height:1.5ex}.CodeMirror .source-msg:hover{text-decoration:line-through}.CodeMirror-hover{outline:1px solid grey}.CodeMirror-target-line{background-color:#ff0}.CodeMirror-search-match{background-color:#ff0}.CodeMirror-search-alt-match{background-color:#bee}.CodeMirror .trace.call{background-color:#0f0}.CodeMirror .trace.exit{background-color:#0f0}.CodeMirror .trace.fail{background-color:red}.CodeMirror .trace.redo{background-color:#ff0}.CodeMirror .trace.exception{background-color:#f0f}.Prolog-breakpoints{width:1em}.breakpoint-marker{color:#822;padding-left:4px;font-size:120%;position:relative;top:-.2em}div.edit-modal{position:absolute;left:0;right:0;top:0;bottom:0;z-index:2000}div.edit-modal>div.mask{position:absolute;left:0;right:0;top:0;bottom:0;background:#000;opacity:.2}div.edit-modal .goto-source{position:absolute;padding:.2em .5em 0;border-radius:5px;border:1px solid #000;background:#fff;box-shadow:10px 10px 5px #888;z-index:2001}div.CodeMirror-dialog{border:1px solid #888;background:#f8f8f8;box-shadow:10px 10px 5px #888}div.prolog-query{height:100%;padding:5px;background-color:#eee;position:relative}.prolog-query-editor .buttons-left{display:block;position:absolute;bottom:10px}.prolog-query-editor .buttons-right{display:block;position:absolute;bottom:10px;right:5px}.prolog-query-editor div.prolog-prompt{position:absolute;top:5px;left:10px;heigth:100%;vertical-align:top;font-weight:700}.prolog-query-editor div.query{margin-top:3px;height:calc(100% - 35px);margin-left:2em}.prolog-query-editor div.query-buttons{margin-left:2em}span.run-chk-table{margin-right:5px;color:#777}span.run-chk-table input{position:relative;top:2px}ul.dropdown-menu.history{max-height:30ex;overflow:auto}div.prolog-runners{width:100%;height:100%;background-image:url(../icons/owl_25_years.png);background-size:90%;background-repeat:no-repeat;background-position:35% 50%;overflow:auto;padding:0 5px 0}div.prolog-runner{position:relative;padding:2px 0 2px;margin:0;border:1px solid #ccc;border-radius:5px}div.prolog-runner.tabled{border:0}div.prolog-runner>a.close{position:absolute;top:-4px;right:-10px;z-index:10}div.prolog-runner:focus{outline:0}div.prolog-runner.iconic>div.runner-results{display:none}div.runner-title{padding:0 5px 2px;border:2px solid #333;border-radius:5px;box-sizing:border-box}div.prolog-runner:focus div.runner-title{border:2px solid #000}div.runner-results{padding:2px 0 2px 0;background-color:#fff;border-radius:5px}span.answer-no{float:right;color:#060;font-size:80%;margin-right:2px;font-style:italic}div.answer{padding-left:5px;border-radius:5px}div.answer.even{background-color:#eee}div.answer.odd{background-color:#fff}div.response{font-style:italic;color:#00f;font-size:90%;margin-left:10%;background-color:#eee;border:1px solid #ccc;border-radius:5px;padding:0 5px}span.prolog-true{font-weight:700}span.prolog-false{font-weight:700;color:red}div.cputime{text-align:right}div.cputime span{background-color:#ccc;border-radius:5px;border:1px solid #888;padding:0 5px;font-size:80%;font-style:italic;color:#060}span.runner-state{position:relative;top:2px;width:1.5em;height:1.5em;margin-right:5px;background-size:100%;background-repeat:no-repeat;display:inline-block}div.runners-menu{position:absolute;top:3px;right:5px;z-index:2000}div.runner-title button.dropdown-toggle{background:none repeat scroll 0 0 transparent;border:0 none;cursor:pointer;padding:0}div.runner-title>button{background:none repeat scroll 0 0 transparent;border:0 none;cursor:pointer;padding:3px 0;color:#000;float:right;font-size:21px;font-weight:700;line-height:1;opacity:.2;text-shadow:0 1px 0 #fff;margin-left:5px}div.runner-title>button.rtb-toggleIconic{padding:8px 0}div.runner-title>button:hover{opacity:.8}span.runner-state.idle,span.runner-state.wait-input,span.runner-state.wait-next{background-image:url(../icons/logo.png)}span.runner-state.wait-debug{background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAACAAAAAgCAYAAABzenr0AAAABmJLR0QA/wD/AP+gvaeTAAAACXBIWXMAAAsTAAALEwEAmpwYAAAAB3RJTUUH3wMfEyg27OEfWQAAAYdJREFUWMPtVsFtwzAMJINMwlHyt0foCIW6gUYQMkJGsP8dRauwH9GQacqiDffThoARR6LE4/EoGeBt/93w6AIG4J3N8FcA7AXVm/BBMDdP8JkIsASqHx20BtMD7bKJiBnAfErc5nzld31wDQKuBuEN3mOjHj+j9GZmVuaWv4xNRHwo+7Kgmxk4dCH/WyDuemDI2cMQIGx5ZaOv+Uz9RQNepfdYqPbzB2/9ekGwAaJ7ElpOuiTooFb7zEQw5Gyejs2TcMgZhpxhJjLRYkcjXv8mgJloQS4gpgoMO4RqsMjNEoSYGADg8XquFgqIs1et0Rm4y8BYqK9rJ+8nrm7//VwY4BDT8oh66w7wdINuY1i36FYDQr+2r5gWRoQBLcxaM71vhGbHtACkGCDEtBp7vJ4rbVhlGvc1g5ujOMWARjlMG3NeQI0xQPj4hG9dzgLeKLMkxRLzbmlBJjUQi5FqDmv/lp9O+LY3mWJAzY7F2JG5PXbBWwaZ9/hc+g3f2lCPW36Xg3nbn7EfAs3X9neMq50AAAAASUVORK5CYII=)}span.runner-state.running{background-image:url(../icons/running.gif)}span.runner-state.false,span.runner-state.stopped,span.runner-state.true{background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAACoAAAAqCAMAAADyHTlpAAAAIGNIUk0AAHomAACAhAAA+gAAAIDoAAB1MAAA6mAAADqYAAAXcJy6UTwAAAAzUExURTxGYTxMaj9FYktZdXSHpT9FYVplamBykExLT4mYtZByMb6gSPrIbO/Sk5OTkw4LBv///4iQZ38AAAAKdFJOUwH4Xfn/K/79yv8b7m9OAAAAAWJLR0QQlbINLAAAAAlwSFlzAAAN1wAADdcBQiibeAAAAAd0SU1FB+AJFQwTJ324eWMAAAIsSURBVDjLjZXtmoQgCIVDSFSy7v9u96DWZO3uM/5oJnvj64Aty2uRr7B8s1iwaP0GjUL0HboqEyn/E8H1KImj+rl/5cKnSzgnYqXuIrDyIxUVaT4DNZRE26vY1/HWRSqpREq4AiKPQP0XBrClnxxX9vgYBkQjcYyEq3rNHGe5mw06TBGVYrZtZiXi3jc5z9XgzlKxWrdtB1yrlUbKHKtLhBCi1W2/1laNyW081AgqbnK/LQEbo/BTN0Qbty3v+wxbFA2vHmGrgsdIa28/Da6mwi//sZH7cSQnj2OwRR9mCaRnZHYcR0dTz22Lty5b15BISs+9dDScKMxCCKYUVu8TkSzROvqxWkbJTIduC2XorIT0+6N0WH/DTpQYfaCZl5QZfzletbdBnLdbPFH0nLfKyP+zTlQqUGiWEUALRJtV2/cXjxJkxKiRF2TPmNGWlpWZdDU8LR/2UbAVCjT9S5rI0vTKc2dRLrXXqoworPRyoa7zICaRXliv65H80quFSjz7RaWMXrXiZGrqiSf16OwlqZZ6lfLUw7tF0vJurVtnDx02Y8069/bKWeM8Lz4xxav/rAA6mHmCfVxwtGDIc5rcZ9/0IDCy1ee1GoYlYztqjuvk3mWGAWSHg8BKKd568C6u5S2EhmaFxgrBtUXoZxDc7dmbalILsLsBLe09HFRHc/gg/XhJ11Hc0CuVwK/D+ubhXaE/VmpWw5foL2fK718FVOGp5p+fGBys6b3/A/dgJEXSAh3eAAAAAElFTkSuQmCC)}span.runner-state.aborted,span.runner-state.error{background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAACoAAAAqCAMAAADyHTlpAAAAIGNIUk0AAHomAACAhAAA+gAAAIDoAAB1MAAA6mAAADqYAAAXcJy6UTwAAAAzUExURTxGYTxMaj9FYktZdT9FYWBykExLT1planSHpYmYtZByMb6gSPrIbO/Sk/8AAA4LBv///y1hUbcAAAAIdFJOUwH4Xfkr/cr+eNcn5wAAAAFiS0dEEJWyDSwAAAAJcEhZcwAADdcAAA3XAUIom3gAAAAHdElNRQfgCRUMAA5e5aCdAAACE0lEQVQ4y41VCZKEMAiUIIQcjv//7TZJHDXubkmVo9FOczRkluVh5BaWN8YGo/UdlOgl1JhI+J8Ivp8UpCRyrh+58OGSHMpCbbEGGU9nfGIWnShQg5JJ24r3E5axFouk+AWoRSB+N2N8kzPHlT0VBoFJdGBkcj9tG3O60gbpVEDkXGqtpeRIETuc4V4N7liKZdu2+gF628pAPvLyEACsn6/VLXscMqsRxDhv2+dqFcTxqRuijaV+JgPWJDyE59I4kVa/DSyK8vAfu/d9V0fu+8BmmWjJYm3uy77vHao93nqNdl2DsuVOmjtUDyhoIQSThnWBMmbJZOR0suZRhtJkQ7PDNfSEmnWkrw2DHeWAQlo0QmJA8UAcv4Ua7Me6QrQGBWtq8sXt84dtDpUGbQ10YfWsazkXiDUlQHRZFbEAfXisWT39XE4oOknDPsqlYpcKAOlXGcVCQjcJUpe17Add0V4DQO+DGKw1S9ZrQpq9CdLcL94DteR78j4QcfLvTQBpy1yoUrOk+SAIESHMtUVvYwjleabxfV4Gskk6+Xf58gVcXdLop4DprbOTtJcxVx9Zv0p2mcRpL0fGgpX4K/+WMTIFP96aeGfepBdaxE6WGBoL9MYudt2J3F2ye7AKujYXioFICBGM6941T4+j8HCytrjP70rzAbte+oHjs/C/mjqrvYaavfrbCMj+oeYfUJ/LX/z/ANqPJNQJtoGtAAAAAElFTkSuQmCC)}div.controller.running>span.running{display:inline}div.controller.running>span.sparklines{display:inline}div.controller.wait-next>span.sparklines{display:inline}div.controller.wait-next>span.wait-next{display:inline}div.controller.wait-input>span.wait-input{display:inline}div.controller>span{display:none}span.wait-input button{float:right;box-sizing:border-box}span.wait-input span{display:block;overflow:hidden}span.wait-input input{width:100%;box-sizing:border-box}pre.prolog-message{white-space:pre-wrap;padding:2px 2px;margin:0;width:100%}span.output.error-context{display:block;position:relative;padding-left:25px}span.output.error-context:hover{text-decoration:underline}span.output.error-context>span.glyphicon{position:absolute;top:5px;left:5px}a.goto-error:hover{text-decoration:none;outline:2px solid #337ab7}pre.msg-information{color:#060;font-style:italic}pre.msg-informational{color:#060;font-style:italic}pre.msg-warning{color:red}pre.msg-error{color:red;font-weight:700}table.prolog-answers{width:100%}table.prolog-answers td{padding:0 5px;border:1px solid #888;vertical-align:top}table.prolog-answers th{padding:0 5px;border:1px solid #888;text-align:center}table.prolog-answers tr:nth-child(odd){background-color:#eee}table.prolog-answers tr:nth-child(even){background-color:#fff}table.prolog-answers tr.projection{border-bottom:2px solid #333}tr.projection th.pl-pvar{color:#800;font-weight:700}tr.projection th.residuals{color:#888;font-weight:400;font-style:italic}.answer-nth{width:2ex;text-align:right}th.answer-nth{color:#888;font-weight:400;font-style:italic}td.answer-nth{color:#060;font-size:80%;font-style:italic;background-color:#eee;vertical-align:top}div.trace-buttons button>span{display:none}div.RIP,div.trace-buttons button{display:inline-block;width:24px;height:24px;background-size:90%;background-position:50% 50%;background-repeat:no-repeat;margin-left:5px}button.nodebug{background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAADAAAAAwCAYAAABXAvmHAAAABmJLR0QA/wD/AP+gvaeTAAAACXBIWXMAAA3XAAAN1wFCKJt4AAAAB3RJTUUH3wQBDQAOjeB7qwAABLlJREFUaN7tWltMHGUU/v7ZYSmXBbpbEDXYGi6VCmpo+2BMDETJQpvyYBVvNGmIIabaGH1Aa3wg6UubGH1Qa9Rq2jRdEqlPmBhSG0LUxhZptlDKStGEWIHtUsp1F3b3P8cHdpYBamEH9kLSk5xkM5OZnG/O951z/pMF7lt8TUT6wNFzI+8w0KAAZz56MffYRgTgBZACAEKIE8GenMNNTYLiBUAx8EyK9oOZD6Fk+EzDV5y0kQBABwAcxGvZluG2xm89lg0FgJkhiUHEYJIVSpLvwpHTN20bAoAW/BaLAkkEIoaUvNsvA22Hv7uRndAAmAEKffmcTBUP2ZJCmSBIyTuFX7l06IuBgoQFQETzAcv5LFjTTdiabQYxQtfoUWb5S8NnfaUJCUDjvUYdIkZWugn5DyaDodEJuRRER/2nfU8nYAYYUoYCJYTdkqqiKC9Nn6XNMkDn6473VCYWAMnhL7/U0zeZsGNbGhQFWpbSSHLry0edLyQQhWgZhfSemmxCaX4GVJMGgpOJ+Pv9TVfqE4dCmoj57p5sVvBkYRbMZhNIEiSxSUo+ue/DzncTAkAoqP+lEhHDnCRQtj0TaSkmTTeCiD+xN146lhAUWo2rJoGyYisy0tVw5ljS+8+9d/HzpiZW4ibicOMKBXUvFwIoK7bClmXW95C32sd+O13e1K7GqQ8QpORVZ0IAKCu24QFrSrgAyCDV+UeUH8oPtm+Kj4iX9IGVnBh4qtiKvNy0cBYlUc20iX96pv5XSwwBkI5GkTkzUFpkRf4jGQt0Ii6flr4LO19t3xLTUYIiEPNiEIzHCzajpNCqzU4g4t0+Eegoeqn14RiJmMJUMuoFWzPxxHbb/GguGcy0Q1WTfi55pS0vNp1YsqEM6L1wWyZ2leSED+YMPEaCv4kkHtW4iOeBrNWIF7+DBYuoA1ioImsD4Pr7Drpdo9AwCMClkPJGVAHIJQI2dCQFw3l9FAODE/rLF83JyXudpyrGo5sB3RwkDWyDmIA/em/hn6Ep/XKqTVXFfuepiplI36caLaNS0jL+rubZzm43Rm7p4xQtIjhR191c6zeSTYMijpxCQUm47HRj9I5Pf/lkX3DiTbTUSqM6iomI/QHC5asjmJic01ebj12OqkZArKkSGKDQ4g68ks35JTqvujE149dvZD9wOaqPr8c4bUDEq+8D3tkgunrc8PqC4cchxNt9DvuX63WgMVxGpbw3hWa8AVzp9WBuLhx8gBkHXc12x3qeyAxoYGUKTU374ewbRSCgaVP4WEGt66z9x/U+ExurQlI7kS2/Pz45i2t/3oZcuDnJkDWus3s6orGVMN4H7pKB2+Oz6P9rTB+8h4Wodjn2dEVrL2RQxMv7gGfMi4HBcZBkbbK8SRCV/Q67K5qbOcMa0IvY7ZnB4NBkOHgAN4SQlf2OvYPR3o0appAGZMg9gyH3lD4bThPUqmuOKncsttMGRTwf/L/uGQwvDr4rEKTqvpbnPYiRKWsR8YgueAG0pU4Hnh1o2ROz4A2eiWnRYmthopys6Wrd50WMzdhuNCRiABACjlSL7fXeFmPjcDwo5CPS6rw4cb3o9wNdX+8KIE5mZBo9AsYBhjjnarbH/a8G9y3e9h/uU+EcypgobwAAAABJRU5ErkJggg==)}button.continue{background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAADAAAAAwCAYAAABXAvmHAAAABmJLR0QA/wD/AP+gvaeTAAAACXBIWXMAAA3XAAAN1wFCKJt4AAAAB3RJTUUH3wQBDDMd/Pc1cgAABW9JREFUaN7tWV1sFFUU/s7sdLZl2+2P2NJfWloDEQIaYhPEhESJBiSBRMODPy+mkYjRBx/EFNE+SFIxGiHhzajAA0GUJ30w+CAqQlECRIEEiKVLW1pK45b+7e7M3M+H6ZRZdpew7SysSU8ymUzunXvvN+ec73z3DjBnczZn/2sTABg/8Fx1QNOLACAWd5viGV6JQTP1WyWv/zwsAj5wAKP7nt8pgnaAIAmAAAlCTd2dZ6ddwdOPIIcJDoM8RbGP2RI4Vtl24sp9BTC2f30EQH2Wi/e0qzv64aTA/rxiIPyddPxs5R7AvnV9BGoAAkbICaqUxSffYcWhrBigrDT9lNuvRyht87ee+SnHIbSuD2ANSBgrXnZA3KPRToDxUdgjEdi3IrCGL0FZca+HFBQ/ebjA2CFbTpu5AKAnhY1SgLLvHb0EIIVl0ArLUFC1HGyKwRw4g3hvF5Q5BpAaRW27YU0u5jd4UTbD9huA5o15wAY480sCBTBqW1G8cguMymW3xyU3DQ4u2c8OaL4DSEpYZftyiRZAUct6FNav9ubOS9crWt7OkQemwogKpO3bFaxfjYKq5dMsJsBHvXta6nzNAS+LJK78CIikoUo67KQVQHQD0Iughaqgh2sgRvFdJyhqWgt7tA/W2ABAhgJQ7wLwzRMS/fLpXgFr753nvVQJ6KUNMGpbEQhVZpzEGunB6N8H3XGi1UUVlX6xkiaCozNbvNNuRrsxfv4QYn1dGZNbD9dBKyp3xynrnxha41sIhUMPtUXHh3aLZQfEI5EEFkyZ5ksIqQlYbhPlAi4h+STAtSA1QiF+7XcIgOCCx9NOVFC6CPbETaeikxsB+FLgdNl82AZwdiYv39i7tIXAXpDPAsTktePQSxugFZalTlRWD/afdDwJLvOPhWZhlW+ev1KpF24geYx0QirW/2daatX0kDdMF+QFAACQLadNEO+5VGlGuwFaqUVOL/TmWHXeAACAqrcudpEcAAiaE1CTI6ke0AJetVuaVwCcjY3qdtlLmaMZGMkrW3wTcz4VFKpRBUeKKzsOMlW3JcmWfAOgRAjl1BNRVnpVm7TPyDMA7uIdnldOyKR44HZRzD8ASdtOldEDt6k0zwB45YiratODdORInnpgKjxsO60H7hSCeZYDBMSN8fQ5kCQEHxSA7q8aC40R+VSgWknKlLaBIh6RaZ630iexR+1e7QwfBW0ocAoPJ6CsnYveN0/lFEAwqr0AUVvvPGoRb5FSzHA4kCTV16ZIdZE6ACtzWolt4V+kSmQ6yUPAgFZYknaLaZTU3mWfQYA4N6Oz0Wytd3fDM7DVtwDL3MUHSxtghBciUDAPEjAyJro1+S+seBSj/X+AKuE5NMOBuJVoW9qBRM4BAEBkV32zptk/UNRiNyyC4QaEKpcBktmx5sQQopFfQDvuLl4B8k7z9vjuGZ9Oz9SufVZXAds8QuEaNxz0ovkoqV4J0VLTK3Yr4nx5Wu7iJyB4tbk9cWRWx+uzsct7WoJGPPqFAK+4PK8ZxQjXtCLgnNgDAMaHL2J86IK3mA1qgo1N7WbXrP8PzL4KQyK75n8IsT9wqVULBFFS/QQCwWKMDZ5DbKTHm7AXAkrb0Lgj1u3LDw6/rLuz/A0RtQekThCiadCNMBITN70a6Lhlxjct7sBNX2R80pORZY1PSMoHuNoZXkfwEKhKUnmeB7VE4rWmDsS87zz12IWs5v3t7KOSMwAA8E9naAXI70HWTQs8cGdze2JHut9SjXXXs5r3am91bgEAQOTjeTW2UocV2UKqbS3bza8zjjOLeZMWsLA6ktVAPdcb/MkhvwD46YH7BSCp2qxq/DWrcU5c8oe9Vi3Mct7LmLM588v+A+5od3b4azuuAAAAAElFTkSuQmCC)}button.skip{background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAADAAAAAwCAYAAABXAvmHAAAABmJLR0QA/wD/AP+gvaeTAAAACXBIWXMAAA3XAAAN1wFCKJt4AAAAB3RJTUUH3wQBDDc5pJgUpwAABxRJREFUaN7tWWtsHFcV/u7MeNeveG0H2/WTxE4opVQqfamNWsEPVEoiixIwoFaVeKhQgRTSVlSQFLF/SoRQhBASUvkB6kMNWKWKVIkiNUUJCBJC+kpUoVhO7Tp27KS2d73P2dmZ8/FjPbuz3hnHXm9aKvlKI69n7s75zv3O+c65d4HNsTk2x0d6qGq+xNG7GuLpSJeirZU/MX3na/lsYst3X19QCvxQHIj/fs+gptvfUMRegoMg2wCCIEACIEhZ/lv4H1z5nARkgeQClJxW5AnHUSc6f/DG+DVzIPnsnhtAeQrglysArQ88ACk9L5/7bxK/6ni/7c8qetyuiQMcHdHTuewhivMoQKMCkKZDGQ2AKgHxB19wFbYJyWcBOoFzSZmCyHe69v332IYcuDI60txopl8gOVw0oggtsg361h1QkV4ovb4quulYYC4BO/4enKX3kF8YA20ThLiLIxD5ZWe4+afqe6/n1+0AR0dCaTNzjJR7XPCqpRdG3x1QDe01VxDaJqzZMzCnT4JWysvM0a7rxr6qvgZnzQ6QUJnn9vxJKCNunOp9t0PvuPGaSyHtHDLjf4F1+e1iWJF8oTs2/pCKQlb7ru5++NHQ7m+SPOCuvN7zGegdnypQe40vpTSEtl4PgMgvTRbugTclGyPxw6/ET12VAT493Jiqt8cA9oKEatsGY2DXh1KY0mMvw5p7082LtGj5T/btm5kOmm8AQLLe3q+WwbOuHkbvrcuKEUC5lYEkp+Gkr4BWBnRygJ0vSOWy9njVhlBQdWEoownGlh7obUPQ6vyFoHHoC3BSM7CTsyDYpBz9CQD7AhkgoVLPfnESlAGCMHpuhdY+6A9cLOSnz8BZHAfprFXnS1K5rDZKDyHcdxfC3bf42rGXJrF07nn3/fHZxs7O2wJUScs8c+8tLnjoIWitA4XVX3nZWVhjr8BZGNsQeIAQ20R28m8wp/7ha8to6Yde3+a+q7U7M/vZwBAS4H7XiNbcBVDg17Hkp09DsjFvQTsulFeVkvMCNQ9HUuWpZRc/CRiGSCc03ETh1wHeCBLZmVMwWrfBaOqqsBdq24FMZr7gsOBLAI755wDV7UChFVDNHYXVrYj5FOzYhAueUHiw/eFTR6rI0aOMfu7Q5fbZlwgOQ4jc3BvQB++tBBYZAGZOFhZL8dNBL9SoZMjtbZTRBIhTcTmxSU8o8Gj7wyePVKsyKnrcVoIn3XCyYhd8bWp1TaUQFLku0AGQLS44peu+MemYi8X4VcKXNiqVXfvPnwUYIwTMZ0ErWWFTGQ3LiyYg2B3MABguS0if1YCZLD5XdN6pSfWFvOuusJhLlQxougseICPBdcDbEtMBqHzkM19UG8CI1aZ/YMJlXhwTul/ueTrgVQpZqZ8HHdDXAacolbaWz9WIAauAi6DYvuJRLtUBDpRtRsQJ2CJ4db5mm0EW3+uGjh8Ha2OARQZ8Q8hlCKx2G736orjJW2GXHruBDJSqZiADXipVjRwQj11KIANXDSFvyWcAA2uhshoGwOUKxIAcWFMI0ZPtAQyUkryGDhTtSiADLDs0CAohT5OFVRhwWVLI1CoDSjovEtC+exTy6nXAXQ1/OWOVDExEt9WHWp3DEN5BBQVxVU920psDvklcYv7dQ42vFvwQd8uZ0cinDG9L7J9IKLbChKxbg8IR+ysi+D5AQOhtD8qZD0ri0uJ93psTBRyqX/P286TjexXiVapiwFE4B9AqAVkBXgtBC0d87YZa+nwOyEoYqPC2UaHHAn8q3TnrTIH+/dNnpw/37ib4IiitLqBw5OMIt26HXtcApRm+DET67oa9NQbbjCFx6TRAy/v4edliPaKVFQu/nVjF7mv9o+/xmdfoOLcJeN59lxmfQC52AUppq9gVUCwkZ/8DiuXRX7V/6KD10M59yGllxcKvE/X0QRupAwNPXLmgaeYugCfcd5lLE0hc/Bdo53ztmvEJxCZegzjF9isDhZGhg7lf+7YS2blzvnvYsmq9gdH/WGLxUrRnt91kPkdyL0lYmctYuvh3tPTcCc0IF+dmY+NIzL0FT0wvakr2bj9gnyjfD5DWahvwlRv0XF15IK539EQvZfrTiyMkD7s6nzdjiE0dh23GQbGRvPwWEnNvesGPK1G7VoIHAHXltzcfUODPCIauAl5APtP9w/Fve85SG9DQtmZlVcO/K5OAiUPNjyiF35A0CEJpOupCEeQy73vCVf3Tzufuvz6K+Zr9QrOiy1vzSLz8QEfL8JH5ciea7iNkFMQWH6n8o5a3vrU9GvDTDwDtAz03TKYqbm3/SfqvEO1ugBe94En8fPCA9cBq4ItHi9WOe24440zNd+vr8MD37uDB9NmpXzTembedUSjuBPDjHQfzf8CT1/5gfF3H0ImnP/GxWiP4QEMo5RNCHykHHC0l2Byb4/9r/A9GxF3/Bu0ZYwAAAABJRU5ErkJggg==)}button.up{background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAADAAAAAwCAYAAABXAvmHAAAABmJLR0QA/wD/AP+gvaeTAAAACXBIWXMAAA3XAAAN1wFCKJt4AAAAB3RJTUUH3wQBDDYM6zDhxQAABQZJREFUaN7tWW1oVWUc/z3n3JdtXudUzBfyZcuRaUVSmbVerDQLC0FIkCAR+1YIUhLNivslqm9ClrhR2ZQopPrSlyAQMZGQymXZjERN0d07d9e2u3nOPef5//pwPHdznqsbe+buwD8cuFye8zy/3///+7889wJlZp3Nj6RzTcv7O3c/2ExC3Wi9VW4EFGUrqStJeaVj133vTTgCpI6TAlID0G9lP1q8aYIRCMCTGhSBQJrbd9Y/P5EiUARPaoBiU8uX53bU3hspufEEm/14RcpOXK6xPUm4AAAHCviTIhWkhmUnob18SOQUtL98zhsXLo0Lgb4vVi7VmquE3lMk7yd1DSixwOMS5XlU3bUOfW3fQnwHpIZQDuve5Mra9Bkn3Dc21sDzn69+VqAbfS2PBSBZBHg98KSGshJILdmA7tZPQQpA3aCqej4j8ZJS4JgS6Nz3XHXCkxaBrOUQsCFAKAuIVUApACIABQoDa2KTZ8GqmIZU/QvoafsmIAVuOPtB9T9Az7tjJqHuvasXWoLvKXJn6F0oC/bUOljVc2CnZgGJFJQ1fP/1tO1H/9mDoGiQQtLfWNfo7DVOgC3PTMqL+pmUJaHX7RmLEJ+9FIhXjmJnQdcvTXCyv4eSc6nkaeNltFfUJyF4QCFe+zjitz8E2AlA9CgeYso9G6Hik640OSQVrTeN5kBfy6oHtJaXQ9nE5zXAnjIfoBjZ//L5Q9Bu1+AiesAoAdFqK+mD1LBr5sOeugAIvDVqczqO47+2/YO/2lfX6O4wRiDf/PRMTf/FsFTaMxYFob9evoiGOF3QTi5ITt8BKVBKITl9EVS8CgBQ6DmHXOsegAzegzroeu5mpUBjBHxLngAlTgpU1TSoZHWo1YhxwYd7/iiczK+QQt81/QAU2JUzMH3ZFminC52/7Qa1G75+Mum56xamUTDaBwhpCOu7Pem2krqn5yB/8jv4+YtgRDMDBRQNL38BLPQhd6wZUugNNd8hgjVz08iZ78SU5SEAq3JaSfn0n/5xKPgsoY8R0g3qbopsJkWRGrnje+Dl24s5LEqvrX/HPzV4P3MRoJ4ZRsCKV0Umr+7PopD7OwQvQv3a3LntTWo9iotPv5/aRGqb1HC7ilhFERvrt/tHhu5pMgJTQznAsiMJuJfaBo0TbJn3evuuUuP0EGuse7uwf8zuA0yviJF6MikggioS1Yz83otFzQv9r0rdB64el1XTHdsLH5Y620gEMnW5ZKw/roKZR4EkEAyLV1eqy5eKEdDC1pL1YODDD/967qs35Uo5eCQG9bWP+BDfDdfJgm0dmWj06vCVD630CuufTMO/3rkxowREACWRFYjiIezSgPSH8/xQSyXcNflCxTLXd44uSSN/o3PNEMgArLxyCYGKHh+0N7jOe6W2mrUNfYBzYLhHG40AKIFbo5oYpdikaGi4M11GEY7QjJIQdRE8DQ145nOAOqgLUQCHjgzlSUCC4hdJwDx4gwQyIJMDEYiag8Q8+DGMgERKaCzMIIGB5IzyNMufgB7oAyUkVPYEgkRFySpU1gTCJgWlSuQAyzwCxQ47YSUkxW6b+etr3CwzMk73JjM+qTn8SsNCWRGo3wIX9HcCGA6DApTaYYrAVT/uPnr3iRFl2k9/LFamBDhC2CoyB85nazAe1rD4+IjWHz5RIonPZGePCwGKb0ZCownleEmo7P5mHVUfeLj20IhePnIat+yWTXT7H9J2ChlDGcHsAAAAAElFTkSuQmCC)}button.retry{background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAADAAAAAwCAYAAABXAvmHAAAABmJLR0QA/wD/AP+gvaeTAAAACXBIWXMAAA3XAAAN1wFCKJt4AAAAB3RJTUUH3wQBDDgagWd5GgAAB1NJREFUaN7tmVtsHGcVx3/nm9n1+hLHzj2NY9eNMWqFBK1DUAJSIhRAQqqoCjU0IkUgQXkBBVUUpebBCBR4qaJGQmpA3ITKLShUsgJ9KWoVKanS0kJL1KYkcZr6Ejtq1vb6speZ7/AwsxfbMxvb2QQq5ZPGs96dnXP+5/zP/5z5Fm6v2+v2el8vuRk3VUUyP+tZaxP1zdFXpOZfL65taZwck97Tc7ccwPhP7+tyHN2tIrtRs0NE1oJZKyICAiJIeAZBSmfDvM+D12lBLqpw3PruH1q+duLiTQGg/Xvcq+vTnxfhO4h8rNKx8mtTfm95ICqv/Qti+lY9cuLNmgEYO3L3Xoz5hYhpj3MMcTCJenBToWNUASGggnpziPWjQHhinMONdfUHpfeYv2IAerQnMZ6b/iHGfBfEBEYM4qZIrO3GWd2B29KB1DUjTnJlteNn0clh/PfOYycvIToP8MBsqnHfht5j08sGoH/CGbvS/WdEHihGTZJNpNp2kty8HXFTtReCuWt4Q2fQqeEKEOZkY6phr/Qeyy8ZgPZjRlu7fisi+4ppTW78MA1dn0Xcupsuk/7Vs/hDL5fqy4g51rD/xBdF0CUBGDly5wFR53CRm/Udu6nv2HNLtd4f/zf+yGuVdPpq0yN//fV1AQwd2dJmbOItRBoFQ3LTvTR23/8/aVje5VNo+lIRxHBT1u2WRwdm3aoa6zuPq2ijKDirNtCw7TOgfuS1tpDFT1/Ay4yg3gxayBFkeYHEAmDATSBOHZJswGncgFnVhiQbYn1xtvRQmL6CFLIgbMmkvAPAoVgArxztSTA7vh8FFWi485OBcbsYQG70VXJDp1E/T1GdYiU2ok948hYiDs6aLhJt2xGTjNB7wV1/D97IPxAFEXlUlR+bOACbZ0d3q2oLKE6qFbd5axD9BUf28knmLv0d62UBBVUUG56D/0HR8Fx+bcvvqaLq47/3Nvm3/wbeXKQt09IOTjK8r22f/c2n74vNgLV8TkRRhWRrV2TkvZkx5oZfQgKmoMpZMfwRq2+okXEDucBBgESApQjCdZoM/jqr5oNGzKdQ9qiAnUtTGDpDYuvOSL9M00bsxGVUwMID8TUg+qGQwrir29EI7ueuvArWoiKIysDGa5selP4XvBXU6KFrP9/5MKrPqCBeehBnwz1IsmmxW03rYeKdMCjmo7EUwtpNRQqYRGOQgQVHPn2hRAGxfH+FzgOw5uunf6/os0Xq+elLkTbFbQwohKJit8UCUHQzalEUcesX8VHzGbQwF/AdTW88cO71G57trR4vBsTPXousA3GcyvpqdqsM9atVQNRijLOoBmx2MgCnoGIv1kLrRf2zVp1AuLKZyLorFz6oUFelD5QuitR+62eDSAiIMlWbduWmwUfVoLYQ3XPUR9UGo7iCG58ADSKhRBawWq8CpOZr0m1NIScqiFjU+pF2A1BaAlE1A6phH4pIJdYvg8RoDefQwC72unZVbXUA4fNtbCrLIG0tB+nQrl2C3aVQKGZ8QINuiwA19L9MXY3NQNGuVquBSpSRNaBeSYWCP7WmkMbWQNlu1QwERRKMLXEZsKiY4NGvhnsyhPyuloFA/eR6GSjKlR85LAWRsFgxNfJ+FiURJlSr1kCgfhb34o8SO6xIn4g0BNO6CXhdGQmNr4Gw2e0aenLzKyBgDKIoRs7kJ5zHOvsvZZebgeCeGmu3UuJdkKcF7g3ac6goKsUGFRbp9SJBM2p7EIOEwx2W7XWrvVPAM8urAIuoCUaUOAphUTWIgFHhX/NpUzGjoySb21D1Fx2mbjWY5Lxri7NTqL15X3hjJTUQPE8QaTc4ys8Trl2V/6bJJF3gyyUdlgTNd+zATbXi1rdGRsIYl9a79uIX5shNDJKbfKdIJ1TMhKh8YeuBodeXWQKQCLMaV8QL+o/5wLfJbevL7wc5UFR0tXkyoy+jNh9y3Y+eDMWQS18gOzFYyoRFz6nvb297bPj5lfaB4r3i7FY+2ZXkY1tf7imEh8I4YP0c6cHnA+ci5nL1cky9e4rs5GAl9V40Jrur/fHxCzfWBwKKRNktjhJFEIsEfPCQu9uqOQ6sCclC86aPUN/aVa4jL8fUyEt4uanSQ7qIHHdnUvvv6B+ZXanrVw/fvdl3/JHFe62xGwWTiwS88wnvRbGyCzgfusvUldfIjP0TtR5edoL05RcoZNMBT4OIPbl15tpDN+I8QC6h+ciNgPiNgnxsCz3Xzzo3Ufcs6MeLGxt1Desp5CdR6yNBBDxVvtV5cPrpeSQY+EbDkr2eS6v0Hiv9sDH6VNcvEfmKhBvIVTKRV+QHVWeAwX5SNpH8FfCl0u5M6WZkBNPbeXDmucrvTA08vK75/t9dXeaz2IpnkaozQGc/2bueyO9T5dCCPvEu1nxiofMAZKZv6Zaju4TYKOT7LhxKnAd+gsp/XMf0tn9vZiT6Gxk61g8v2YH2daP+yTf/j341nDravS4U8WUcK1+m1gCmbzGFag7AN9OW2+v2ev+s/wKIypfbke4fXgAAAABJRU5ErkJggg==)}button.abort{background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAADAAAAAwCAYAAABXAvmHAAAABmJLR0QA/wD/AP+gvaeTAAAACXBIWXMAAA3XAAAN1wFCKJt4AAAAB3RJTUUH3wQBDTcgwTHWUAAABeFJREFUaN7tWU1sVFUU/s69b+Z1eJ15pbUF6gCagIFEWFgXXRhRSNCVisRuXECFDRsSY4IhcdHERGITQgKJuoBUVyaQKK40xhYlXbCgmyaKEgP0Jy0ghb5pp/P33j0u3kz72s5M3512xEXPcnLn3u875zv3nnMesG7r9nTs8nuQ/4e9qJY/OX0HXgewy+7u/3K14PlsZ2y2pfEIg/9KHO2/VncCTt+BV5nVBYCaobjXdjIX6aMbmVrBO3bsOASdEkRJBvbZ3f3X60agBJ5I7AUAZh6vlUQQPBElSz8DeE2HhAi7MHVp/6EgeAAgoiQEnXLs2HE+2xlbJXgAIGZ1IXVp/6E1JZC6tP+QIu4pgadYC8hqq4lEOfBktYFiLcX9xF5F3BOWBOnKhho3w2jvAEkT7uggPGcMZJih5FQOvLC3w2jvAHs5uBND4Nn70JGT0JFNCbxMJCGsVhjbXoFseSFUJKqBF1YrZCLpO6Zxs5acSNfzMpFctE6l/4E7MQTljKBSYq8EPmhealwrEhRK8xXAhyEBAGHBVyLBrIYFU0/i2MD3KxKY7tv3Jlh8HkxYY2tnRfDVSJCrzjEBkOLDsOAXkRi7Ac5MzZMAqY+bun/7KbjOWI5EbARR80KWSJA0V77OrFYY7R1wAXhTt0GGmUREnhXki4A1wAPwzxTBCoOaJUWeWzGJm45d+5aIPpvn44zBHR0EWAHCqE4ivgXRHQch7a2AmwMVwSs3B2G1hQZfiianHy5Ikri3ccPsN0vXli2izry/6fdswXgAxh6SRoILaai5KZAZB0WtKpe8AmQEsmUnOD0JlXkMVh6kvRXRXW+DGpr8NZpSBHGvbWUuUtfy67niLcSXO2NOOnYcHD75fKkwQACnH8GdGPJ1qun5sOBXfMi0SATAU3FblXV8aTXYdQEf6iXWIUFF0TPrVaW1gg9VC1HXjYxtZS6CuJeZx/3EHvHlEUjsmsALY1XgtcrpspFIbINs74BobJ2XzX/lee1yelkkmOFNj8CdHAKnHz0V8FoEgiSI1TlmngYB7Iz6QIoJGwp81lkMXqlpQJ3TBa9NoERCSGNOSNEkiMBuDpxzIMx4+EPNODjnAJ7/2JEQTUQyowteu6XUqSrDSKgwcRPKGQEBYEZN7alWBGZbGo8IQ5wXREkulgfRHQch4lv0vEaATGyBueMNSGsT2M2DiJIkxflUs3V0zSOwlp4vvXrM/tUbpp9YFYF6gtdpimqWUM2yEYb/0BUfO6ISaFoEPljFCqsN7Oa05ET18nzJqwvF3DPLPK/T2VWKhKiX593RQXhTt6Ee34Y3NggwVwVfaySoXp4PeBEgQCa2w3j25drL6gqRkEunxMkXdx6GoJ7g0CmS7KzxYDUNIEtEDZxLgQtzoAa7elMEgKIWqMGGykwBhTSIKAHCnlyDMfaSee/WlT/AZSXUdQWekOK+KI37mIFcyj9QRkPLhkp3vZCnifhTZoyj2CuHak9l1D8zlypKz587kRD3u67Aq9pSnrl6997pt54fZvBuIrEJyoVKPwRFYhBmorznZx+gMDIINTMBEgaYeZzBnySsuT4z6t7MFYyMTnvqOSMojA6Cs9MAUXGsghP2BwM/ag22APwKgOAVQGYc0d3vgja0AF5+wfNeHvk/f4DnjEEYZqkjOxE/+stXS/Y7AeALAGA3N98nQ0YB5c57nuemkL/1HTg3AzIiYK4+2Kp4C9nd/ddJ8WFmNQwZAbtZ5O8OwHtyZ8HzM5PI//2zHyHDhGIeV6xOlpseJKz01wx1kpnHyTCh0g/9/85MLnj+yR3k7w6A3SwgI1BKDZPiw9Xmoyu+xJWmdCRN7Xq+Wnu6dLhbbRqnXQuVG69DyGVzmzD1fDkSZLUByls0hQsDXqucXpQTHJg+VNB8iP3mc6I0uiNBK2p+1Z+YSiSo+O9awJcjQQRt8Nr9QDCxqyVsWAsmdpiEXZOvlPMTbCU22vHM1VrawGU5MRN7B0I9WTp5rqut5YfudVu3p2j/AkT4owo7DZieAAAAAElFTkSuQmCC)}div.RIP{background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAACAAAAAgCAMAAABEpIrGAAAAIGNIUk0AAHomAACAhAAA+gAAAIDoAAB1MAAA6mAAADqYAAAXcJy6UTwAAAAzUExURQAAAAUHAmNlaKSkpXtpZllZWVx9LsHLo9bX2Wx9jpazUak9Lu3s797g33SZKnybRP///5NI/qoAAAAHdFJOUwVE/v+8OP47SgHcAAAAAWJLR0QQlbINLAAAAAlwSFlzAAALEwAACxMBAJqcGAAAAAd0SU1FB+AJFQwBEyT4/QUAAAFbSURBVDjLdVKBooMgCGxggQj2/3/7DnNb7m2kdspxgLVtN3sQw8r2y4glCaw/KAW+WivRD5EHK1trrTSqun8TcNWWjFYr0zcBD1FuxtyQ5NO9K2oTlYYyCDmYZcnC6u5wqzAJt1Kx9ZvKHsivWtu0wqLht16QXjULuGwnTv5Ngl2H5vSPDCErocAq7mnHq1IplAqPO4E0qOCqK26aIkrhVYGSgDAqAeyJF4Lj0C/SIACvNcBBWXtUyCeuHEsNUyGdUKm+tpmfgWo4ZtScSPN5D3FFP6f/J7wMPh8CH10oDq8xF12LRKhex8Od1FhT4GNkAs2RD7Yu7y7s6IfNGq5CjuPobwU7JaIboqz3nqTTQqy/auhiZgJfN5Hk9DxJlP/dfp7d8jklh2GRwR5BEEkwouY71wQ2ECrsUICN5WZznynyjS7GGDg7mLsDCjd7bmb3LwQ8xjbXx/bG2x+HDRcuxXGCugAAAABJRU5ErkJggg==)}span.depth{display:inline-block;font-weight:700;background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAAUAAAAUCAYAAABF5ffbAAAABmJLR0QA/wD/AP+gvaeTAAAACXBIWXMAAAsTAAALEwEAmpwYAAAAB3RJTUUH3wQBDjQRuYQ78AAAABJ0RVh0Q29tbWVudABEZXB0aCBtYXNrQcBmawAAABhJREFUGNNjYEAD7Wdr/zMxYAGjggMlCACJuAL3jmFt7AAAAABJRU5ErkJggg==)}span.port{font-weight:700;padding-right:.5ex;margin-right:.5ex;background-color:#ccf;display:inline-block;width:11ex;text-align:right;border-radius:5px}span.port.fail{color:red}span.port.redo{color:#ff0}span.port.exit{color:#0c0}span.port.exception{color:#f0f}div.prolog-exception{color:red;font-size:80%;margin-left:5em}div.controller.running>span.sparklines{margin-left:.5em}.jqstooltip{-webkit-box-sizing:content-box;-moz-box-sizing:content-box;box-sizing:content-box}div.render-multi{position:relative;vertical-align:top;background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAABQAAAATCAQAAAA6heU+AAAAAmJLR0QA/4ePzL8AAAAJcEhZcwAAEMQAABDEAbRyZ/IAAAAHdElNRQfeCg8LIivxaI+JAAABT0lEQVQoz33SsW5SYRgG4AchbSkcYrVpo6bGoXFydvMK3HsJLt6Ct+AFeBVunVx0cjFODvofqyDQFDVttef8cg6IA4SkFXjX70ned/gqk4kV+SUVnGs8rayC54KA/e7DvdpydiZIJXbEJyyFp4IjW27IFG+Xwp9SR266LhM/PT5dAn9IfbGtJROtP2ch/C711bZELmrYOFwIB1JtOxpyfzQl1n4vgANBx65NuaGmlsR69h88EXTcUpcpNLQkknJ3dAUeS327wlr+fpxe57Av6F1iLYmxOLgEe4K+2zZkitm2xFgumsOJrs/67liTGc4qm8YyUbw7gxNdwbE9NZlixhKlXBTl+1NYaU9SPfdU5Ubz0inL5aJya3h2oBa03XdNZqzZaR5uvq5/mFyUcVSUo0JRLerlxQFqwQPVN/FF+T4Jj0YL32ial8/eJfDK6vwDMhCTheu9OHEAAAAASUVORK5CYII=);background-size:15px;background-repeat:no-repeat}#render-select{position:absolute;background-color:#fff;padding:5px 0 5px 20px;border:1px solid #000;border-radius:5px;box-shadow:5px 5px 5px #888;z-index:500;white-space:nowrap}.render-selecting{outline:1px solid #800}.render-multi-active{position:absolute;left:0;top:0;width:20px;height:20px}div.render-item a{float:right;padding:0 10px 0 10px}div.render-error{display:inline-block}div.render-error span.error{color:red}pre.console{padding:0 9px;border:0;margin:0}span.format{white-space:pre;font-family:Menlo,Monaco,Consolas,"Courier New",monospace}a.download{margin-right:5px}a.download span.glyphicon{margin-left:1ex}.render-table{border:2px solid #333}.render-table td{padding:0 5px;border:1px solid #888}.render-table th{padding:0 5px;border:1px solid #888;text-align:center}.render-table tr:nth-child(odd){background-color:#eee}.render-table tr:nth-child(even){background-color:#fff}.render-table tr.hrow{border-bottom:2px solid #333}.render-code-list{color:#040;font-style:italic}.render-ellipsis{colour:#00f;padding:0 5px}.render-svg-tree{padding:5px;display:inline-block}.render-svg-tree svg text{padding:.5em .2em}.render-svg-tree svg g.collapsed g text{padding:0 .5ex}.render-svg-tree svg polyline{fill:none}.render-svg-tree g.noleaf text{font-weight:700;fill:#00f}.render-svg-tree g.leaf text{font-weight:400;fill:#000}.render-C3{display:inline-block}.answer svg{vertical-align:top}.render-graphviz{display:inline-block}div.R.svg svg{overflow:visible}.fold{display:none}.pl-ellipsis{color:#00f;text-decoration:underline}.pl-functor:hover{color:#00f;text-decoration:underline}.pl-infix:hover{color:#00f;text-decoration:underline}.pl-var{color:#800}.pl-ovar{color:#800;font-weight:700}.pl-anon{color:#800}.pl-avar{color:#888}.pl-var{color:#800}.pl-atom{color:#762}.pl-functor{color:#000;font-style:italic}.pl-comment{color:#060;font-style:italic}span.diff-tags{margin-left:2em}.diff-tag{border:1px solid #ddd;padding:0 4px;margin-left:2px;border-radius:5px;background-color:#e1edff}.diff-tag.added{color:green}.diff-tag.deleted{text-decoration:line-through;color:red}pre.udiff .udiff-del{color:red}pre.udiff .udiff-add{color:green}pre.udiff{max-height:30em;overflow-y:auto}/*!
  * StyleSheet for JQuery splitter Plugin
  * Copyright (C) 2010 Jakub Jankiewicz <http://jcubic.pl>
  *
  * Same license as plugin
- */.splitter_panel{position:relative}.splitter_panel .vsplitter{background-color:grey;cursor:col-resize}.splitter_panel .hsplitter{background-color:#5F5F5F;cursor:row-resize}.splitter_panel .hsplitter.splitter-invisible,.splitter_panel .vsplitter.splitter-invisible{background:0 0}.splitter_panel .bottom_panel,.splitter_panel .hsplitter,.splitter_panel .left_panel,.splitter_panel .right_panel,.splitter_panel .top_panel,.splitter_panel .vsplitter{position:absolute}.splitter_panel .left_panel,.splitter_panel .right_panel,.splitter_panel .vsplitter{height:100%}.splitter_panel .bottom_panel,.splitter_panel .hsplitter,.splitter_panel .top_panel{width:100%}.splitter_panel .left_panel,.splitter_panel .top_panel,.splitter_panel .vsplitter{top:0}.splitter_panel .bottom_panel,.splitter_panel .hsplitter,.splitter_panel .left_panel,.splitter_panel .top_panel{left:0}.splitter_panel .bottom_panel{bottom:0}.splitter_panel .right_panel{right:0}.splitterMask{position:absolute;left:0;top:0;right:0;bottom:0;z-index:1000}/*!
+ */.splitter_panel{position:relative}.splitter_panel .vsplitter{background-color:grey;cursor:col-resize;z-index:900;width:7px}.splitter_panel .hsplitter{background-color:#5f5f5f;cursor:row-resize;z-index:800;height:7px}.splitter_panel .hsplitter.splitter-invisible,.splitter_panel .vsplitter.splitter-invisible{background:0 0}.splitter_panel .bottom_panel,.splitter_panel .hsplitter,.splitter_panel .left_panel,.splitter_panel .right_panel,.splitter_panel .top_panel,.splitter_panel .vsplitter{position:absolute;overflow:auto}.splitter_panel .left_panel,.splitter_panel .right_panel,.splitter_panel .vsplitter{height:100%}.splitter_panel .bottom_panel,.splitter_panel .hsplitter,.splitter_panel .top_panel{width:100%}.splitter_panel .left_panel,.splitter_panel .top_panel,.splitter_panel .vsplitter{top:0}.splitter_panel .bottom_panel,.splitter_panel .hsplitter,.splitter_panel .left_panel,.splitter_panel .top_panel{left:0}.splitter_panel .bottom_panel{bottom:0}.splitter_panel .right_panel{right:0}.splitterMask{position:absolute;left:0;top:0;right:0;bottom:0;z-index:1000}/*!
  * Bootstrap v3.3.7 (http://getbootstrap.com)
  * Copyright 2011-2016 Twitter, Inc.
  * Licensed under MIT (https://github.com/twbs/bootstrap/blob/master/LICENSE)
- *//*! normalize.css v3.0.3 | MIT License | github.com/necolas/normalize.css */html{font-family:sans-serif;-webkit-text-size-adjust:100%;-ms-text-size-adjust:100%}body{margin:0}article,aside,details,figcaption,figure,footer,header,hgroup,main,menu,nav,section,summary{display:block}audio,canvas,progress,video{display:inline-block;vertical-align:baseline}audio:not([controls]){display:none;height:0}[hidden],template{display:none}a{background-color:transparent}a:active,a:hover{outline:0}b,strong{font-weight:700}dfn{font-style:italic}h1{margin:.67em 0}mark{color:#000;background:#ff0}sub,sup{position:relative;font-size:75%;line-height:0;vertical-align:baseline}sup{top:-.5em}sub{bottom:-.25em}img{border:0}svg:not(:root){overflow:hidden}hr{height:0;-webkit-box-sizing:content-box;-moz-box-sizing:content-box;box-sizing:content-box}pre{overflow:auto}code,kbd,pre,samp{font-size:1em}button,input,optgroup,select,textarea{margin:0;font:inherit;color:inherit}button{overflow:visible}button,select{text-transform:none}button,html input[type=button],input[type=reset],input[type=submit]{-webkit-appearance:button;cursor:pointer}button[disabled],html input[disabled]{cursor:default}button::-moz-focus-inner,input::-moz-focus-inner{padding:0;border:0}input[type=checkbox],input[type=radio]{-webkit-box-sizing:border-box;-moz-box-sizing:border-box;box-sizing:border-box;padding:0}input[type=number]::-webkit-inner-spin-button,input[type=number]::-webkit-outer-spin-button{height:auto}input[type=search]::-webkit-search-cancel-button,input[type=search]::-webkit-search-decoration{-webkit-appearance:none}textarea{overflow:auto}optgroup{font-weight:700}table{border-spacing:0;border-collapse:collapse}td,th{padding:0}/*! Source: https://github.com/h5bp/html5-boilerplate/blob/master/src/css/main.css */@media print{*,:after,:before{color:#000!important;text-shadow:none!important;background:0 0!important;-webkit-box-shadow:none!important;box-shadow:none!important}a,a:visited{text-decoration:underline}a[href]:after{content:" (" attr(href) ")"}abbr[title]:after{content:" (" attr(title) ")"}a[href^="#"]:after,a[href^="javascript:"]:after{content:""}blockquote,pre{border:1px solid #999;page-break-inside:avoid}thead{display:table-header-group}img,tr{page-break-inside:avoid}img{max-width:100%!important}h2,h3,p{orphans:3;widows:3}h2,h3{page-break-after:avoid}.navbar{display:none}.btn>.caret,.dropup>.btn>.caret{border-top-color:#000!important}.label{border:1px solid #000}.table{border-collapse:collapse!important}.table td,.table th{background-color:#fff!important}.table-bordered td,.table-bordered th{border:1px solid #ddd!important}}@font-face{font-family:'Glyphicons Halflings';src:url(../bower_components/bootstrap/dist/fonts/glyphicons-halflings-regular.eot);src:url(../bower_components/bootstrap/dist/fonts/glyphicons-halflings-regular.eot?#iefix) format('embedded-opentype'),url(../bower_components/bootstrap/dist/fonts/glyphicons-halflings-regular.woff2) format('woff2'),url(../bower_components/bootstrap/dist/fonts/glyphicons-halflings-regular.woff) format('woff'),url(../bower_components/bootstrap/dist/fonts/glyphicons-halflings-regular.ttf) format('truetype'),url(../bower_components/bootstrap/dist/fonts/glyphicons-halflings-regular.svg#glyphicons_halflingsregular) format('svg')}.glyphicon{position:relative;top:1px;display:inline-block;font-family:'Glyphicons Halflings';font-style:normal;font-weight:400;line-height:1;-webkit-font-smoothing:antialiased;-moz-osx-font-smoothing:grayscale}.glyphicon-asterisk:before{content:"\002a"}.glyphicon-plus:before{content:"\002b"}.glyphicon-eur:before,.glyphicon-euro:before{content:"\20ac"}.glyphicon-minus:before{content:"\2212"}.glyphicon-cloud:before{content:"\2601"}.glyphicon-envelope:before{content:"\2709"}.glyphicon-pencil:before{content:"\270f"}.glyphicon-glass:before{content:"\e001"}.glyphicon-music:before{content:"\e002"}.glyphicon-search:before{content:"\e003"}.glyphicon-heart:before{content:"\e005"}.glyphicon-star:before{content:"\e006"}.glyphicon-star-empty:before{content:"\e007"}.glyphicon-user:before{content:"\e008"}.glyphicon-film:before{content:"\e009"}.glyphicon-th-large:before{content:"\e010"}.glyphicon-th:before{content:"\e011"}.glyphicon-th-list:before{content:"\e012"}.glyphicon-ok:before{content:"\e013"}.glyphicon-remove:before{content:"\e014"}.glyphicon-zoom-in:before{content:"\e015"}.glyphicon-zoom-out:before{content:"\e016"}.glyphicon-off:before{content:"\e017"}.glyphicon-signal:before{content:"\e018"}.glyphicon-cog:before{content:"\e019"}.glyphicon-trash:before{content:"\e020"}.glyphicon-home:before{content:"\e021"}.glyphicon-file:before{content:"\e022"}.glyphicon-time:before{content:"\e023"}.glyphicon-road:before{content:"\e024"}.glyphicon-download-alt:before{content:"\e025"}.glyphicon-download:before{content:"\e026"}.glyphicon-upload:before{content:"\e027"}.glyphicon-inbox:before{content:"\e028"}.glyphicon-play-circle:before{content:"\e029"}.glyphicon-repeat:before{content:"\e030"}.glyphicon-refresh:before{content:"\e031"}.glyphicon-list-alt:before{content:"\e032"}.glyphicon-lock:before{content:"\e033"}.glyphicon-flag:before{content:"\e034"}.glyphicon-headphones:before{content:"\e035"}.glyphicon-volume-off:before{content:"\e036"}.glyphicon-volume-down:before{content:"\e037"}.glyphicon-volume-up:before{content:"\e038"}.glyphicon-qrcode:before{content:"\e039"}.glyphicon-barcode:before{content:"\e040"}.glyphicon-tag:before{content:"\e041"}.glyphicon-tags:before{content:"\e042"}.glyphicon-book:before{content:"\e043"}.glyphicon-bookmark:before{content:"\e044"}.glyphicon-print:before{content:"\e045"}.glyphicon-camera:before{content:"\e046"}.glyphicon-font:before{content:"\e047"}.glyphicon-bold:before{content:"\e048"}.glyphicon-italic:before{content:"\e049"}.glyphicon-text-height:before{content:"\e050"}.glyphicon-text-width:before{content:"\e051"}.glyphicon-align-left:before{content:"\e052"}.glyphicon-align-center:before{content:"\e053"}.glyphicon-align-right:before{content:"\e054"}.glyphicon-align-justify:before{content:"\e055"}.glyphicon-list:before{content:"\e056"}.glyphicon-indent-left:before{content:"\e057"}.glyphicon-indent-right:before{content:"\e058"}.glyphicon-facetime-video:before{content:"\e059"}.glyphicon-picture:before{content:"\e060"}.glyphicon-map-marker:before{content:"\e062"}.glyphicon-adjust:before{content:"\e063"}.glyphicon-tint:before{content:"\e064"}.glyphicon-edit:before{content:"\e065"}.glyphicon-share:before{content:"\e066"}.glyphicon-check:before{content:"\e067"}.glyphicon-move:before{content:"\e068"}.glyphicon-step-backward:before{content:"\e069"}.glyphicon-fast-backward:before{content:"\e070"}.glyphicon-backward:before{content:"\e071"}.glyphicon-play:before{content:"\e072"}.glyphicon-pause:before{content:"\e073"}.glyphicon-stop:before{content:"\e074"}.glyphicon-forward:before{content:"\e075"}.glyphicon-fast-forward:before{content:"\e076"}.glyphicon-step-forward:before{content:"\e077"}.glyphicon-eject:before{content:"\e078"}.glyphicon-chevron-left:before{content:"\e079"}.glyphicon-chevron-right:before{content:"\e080"}.glyphicon-plus-sign:before{content:"\e081"}.glyphicon-minus-sign:before{content:"\e082"}.glyphicon-remove-sign:before{content:"\e083"}.glyphicon-ok-sign:before{content:"\e084"}.glyphicon-question-sign:before{content:"\e085"}.glyphicon-info-sign:before{content:"\e086"}.glyphicon-screenshot:before{content:"\e087"}.glyphicon-remove-circle:before{content:"\e088"}.glyphicon-ok-circle:before{content:"\e089"}.glyphicon-ban-circle:before{content:"\e090"}.glyphicon-arrow-left:before{content:"\e091"}.glyphicon-arrow-right:before{content:"\e092"}.glyphicon-arrow-up:before{content:"\e093"}.glyphicon-arrow-down:before{content:"\e094"}.glyphicon-share-alt:before{content:"\e095"}.glyphicon-resize-full:before{content:"\e096"}.glyphicon-resize-small:before{content:"\e097"}.glyphicon-exclamation-sign:before{content:"\e101"}.glyphicon-gift:before{content:"\e102"}.glyphicon-leaf:before{content:"\e103"}.glyphicon-fire:before{content:"\e104"}.glyphicon-eye-open:before{content:"\e105"}.glyphicon-eye-close:before{content:"\e106"}.glyphicon-warning-sign:before{content:"\e107"}.glyphicon-plane:before{content:"\e108"}.glyphicon-calendar:before{content:"\e109"}.glyphicon-random:before{content:"\e110"}.glyphicon-comment:before{content:"\e111"}.glyphicon-magnet:before{content:"\e112"}.glyphicon-chevron-up:before{content:"\e113"}.glyphicon-chevron-down:before{content:"\e114"}.glyphicon-retweet:before{content:"\e115"}.glyphicon-shopping-cart:before{content:"\e116"}.glyphicon-folder-close:before{content:"\e117"}.glyphicon-folder-open:before{content:"\e118"}.glyphicon-resize-vertical:before{content:"\e119"}.glyphicon-resize-horizontal:before{content:"\e120"}.glyphicon-hdd:before{content:"\e121"}.glyphicon-bullhorn:before{content:"\e122"}.glyphicon-bell:before{content:"\e123"}.glyphicon-certificate:before{content:"\e124"}.glyphicon-thumbs-up:before{content:"\e125"}.glyphicon-thumbs-down:before{content:"\e126"}.glyphicon-hand-right:before{content:"\e127"}.glyphicon-hand-left:before{content:"\e128"}.glyphicon-hand-up:before{content:"\e129"}.glyphicon-hand-down:before{content:"\e130"}.glyphicon-circle-arrow-right:before{content:"\e131"}.glyphicon-circle-arrow-left:before{content:"\e132"}.glyphicon-circle-arrow-up:before{content:"\e133"}.glyphicon-circle-arrow-down:before{content:"\e134"}.glyphicon-globe:before{content:"\e135"}.glyphicon-wrench:before{content:"\e136"}.glyphicon-tasks:before{content:"\e137"}.glyphicon-filter:before{content:"\e138"}.glyphicon-briefcase:before{content:"\e139"}.glyphicon-fullscreen:before{content:"\e140"}.glyphicon-dashboard:before{content:"\e141"}.glyphicon-paperclip:before{content:"\e142"}.glyphicon-heart-empty:before{content:"\e143"}.glyphicon-link:before{content:"\e144"}.glyphicon-phone:before{content:"\e145"}.glyphicon-pushpin:before{content:"\e146"}.glyphicon-usd:before{content:"\e148"}.glyphicon-gbp:before{content:"\e149"}.glyphicon-sort:before{content:"\e150"}.glyphicon-sort-by-alphabet:before{content:"\e151"}.glyphicon-sort-by-alphabet-alt:before{content:"\e152"}.glyphicon-sort-by-order:before{content:"\e153"}.glyphicon-sort-by-order-alt:before{content:"\e154"}.glyphicon-sort-by-attributes:before{content:"\e155"}.glyphicon-sort-by-attributes-alt:before{content:"\e156"}.glyphicon-unchecked:before{content:"\e157"}.glyphicon-expand:before{content:"\e158"}.glyphicon-collapse-down:before{content:"\e159"}.glyphicon-collapse-up:before{content:"\e160"}.glyphicon-log-in:before{content:"\e161"}.glyphicon-flash:before{content:"\e162"}.glyphicon-log-out:before{content:"\e163"}.glyphicon-new-window:before{content:"\e164"}.glyphicon-record:before{content:"\e165"}.glyphicon-save:before{content:"\e166"}.glyphicon-open:before{content:"\e167"}.glyphicon-saved:before{content:"\e168"}.glyphicon-import:before{content:"\e169"}.glyphicon-export:before{content:"\e170"}.glyphicon-send:before{content:"\e171"}.glyphicon-floppy-disk:before{content:"\e172"}.glyphicon-floppy-saved:before{content:"\e173"}.glyphicon-floppy-remove:before{content:"\e174"}.glyphicon-floppy-save:before{content:"\e175"}.glyphicon-floppy-open:before{content:"\e176"}.glyphicon-credit-card:before{content:"\e177"}.glyphicon-transfer:before{content:"\e178"}.glyphicon-cutlery:before{content:"\e179"}.glyphicon-header:before{content:"\e180"}.glyphicon-compressed:before{content:"\e181"}.glyphicon-earphone:before{content:"\e182"}.glyphicon-phone-alt:before{content:"\e183"}.glyphicon-tower:before{content:"\e184"}.glyphicon-stats:before{content:"\e185"}.glyphicon-sd-video:before{content:"\e186"}.glyphicon-hd-video:before{content:"\e187"}.glyphicon-subtitles:before{content:"\e188"}.glyphicon-sound-stereo:before{content:"\e189"}.glyphicon-sound-dolby:before{content:"\e190"}.glyphicon-sound-5-1:before{content:"\e191"}.glyphicon-sound-6-1:before{content:"\e192"}.glyphicon-sound-7-1:before{content:"\e193"}.glyphicon-copyright-mark:before{content:"\e194"}.glyphicon-registration-mark:before{content:"\e195"}.glyphicon-cloud-download:before{content:"\e197"}.glyphicon-cloud-upload:before{content:"\e198"}.glyphicon-tree-conifer:before{content:"\e199"}.glyphicon-tree-deciduous:before{content:"\e200"}.glyphicon-cd:before{content:"\e201"}.glyphicon-save-file:before{content:"\e202"}.glyphicon-open-file:before{content:"\e203"}.glyphicon-level-up:before{content:"\e204"}.glyphicon-copy:before{content:"\e205"}.glyphicon-paste:before{content:"\e206"}.glyphicon-alert:before{content:"\e209"}.glyphicon-equalizer:before{content:"\e210"}.glyphicon-king:before{content:"\e211"}.glyphicon-queen:before{content:"\e212"}.glyphicon-pawn:before{content:"\e213"}.glyphicon-bishop:before{content:"\e214"}.glyphicon-knight:before{content:"\e215"}.glyphicon-baby-formula:before{content:"\e216"}.glyphicon-tent:before{content:"\26fa"}.glyphicon-blackboard:before{content:"\e218"}.glyphicon-bed:before{content:"\e219"}.glyphicon-apple:before{content:"\f8ff"}.glyphicon-erase:before{content:"\e221"}.glyphicon-hourglass:before{content:"\231b"}.glyphicon-lamp:before{content:"\e223"}.glyphicon-duplicate:before{content:"\e224"}.glyphicon-piggy-bank:before{content:"\e225"}.glyphicon-scissors:before{content:"\e226"}.glyphicon-bitcoin:before,.glyphicon-btc:before,.glyphicon-xbt:before{content:"\e227"}.glyphicon-jpy:before,.glyphicon-yen:before{content:"\00a5"}.glyphicon-rub:before,.glyphicon-ruble:before{content:"\20bd"}.glyphicon-scale:before{content:"\e230"}.glyphicon-ice-lolly:before{content:"\e231"}.glyphicon-ice-lolly-tasted:before{content:"\e232"}.glyphicon-education:before{content:"\e233"}.glyphicon-option-horizontal:before{content:"\e234"}.glyphicon-option-vertical:before{content:"\e235"}.glyphicon-menu-hamburger:before{content:"\e236"}.glyphicon-modal-window:before{content:"\e237"}.glyphicon-oil:before{content:"\e238"}.glyphicon-grain:before{content:"\e239"}.glyphicon-sunglasses:before{content:"\e240"}.glyphicon-text-size:before{content:"\e241"}.glyphicon-text-color:before{content:"\e242"}.glyphicon-text-background:before{content:"\e243"}.glyphicon-object-align-top:before{content:"\e244"}.glyphicon-object-align-bottom:before{content:"\e245"}.glyphicon-object-align-horizontal:before{content:"\e246"}.glyphicon-object-align-left:before{content:"\e247"}.glyphicon-object-align-vertical:before{content:"\e248"}.glyphicon-object-align-right:before{content:"\e249"}.glyphicon-triangle-right:before{content:"\e250"}.glyphicon-triangle-left:before{content:"\e251"}.glyphicon-triangle-bottom:before{content:"\e252"}.glyphicon-triangle-top:before{content:"\e253"}.glyphicon-console:before{content:"\e254"}.glyphicon-superscript:before{content:"\e255"}.glyphicon-subscript:before{content:"\e256"}.glyphicon-menu-left:before{content:"\e257"}.glyphicon-menu-right:before{content:"\e258"}.glyphicon-menu-down:before{content:"\e259"}.glyphicon-menu-up:before{content:"\e260"}*,:after,:before{-webkit-box-sizing:border-box;-moz-box-sizing:border-box;box-sizing:border-box}html{font-size:10px;-webkit-tap-highlight-color:transparent}body{font-family:"Helvetica Neue",Helvetica,Arial,sans-serif;font-size:14px;line-height:1.42857143;color:#333;background-color:#fff}button,input,select,textarea{font-family:inherit;font-size:inherit;line-height:inherit}a{color:#337ab7;text-decoration:none}a:focus,a:hover{color:#23527c;text-decoration:underline}a:focus{outline:-webkit-focus-ring-color auto 5px;outline-offset:-2px}figure{margin:0}img{vertical-align:middle}.carousel-inner>.item>a>img,.carousel-inner>.item>img,.img-responsive,.thumbnail a>img,.thumbnail>img{display:block;max-width:100%;height:auto}.img-rounded{border-radius:6px}.img-thumbnail{display:inline-block;max-width:100%;height:auto;padding:4px;line-height:1.42857143;background-color:#fff;border:1px solid #ddd;border-radius:4px;-webkit-transition:all .2s ease-in-out;-o-transition:all .2s ease-in-out;transition:all .2s ease-in-out}.img-circle{border-radius:50%}hr{margin-top:20px;margin-bottom:20px;border:0;border-top:1px solid #eee}.sr-only{position:absolute;width:1px;height:1px;padding:0;margin:-1px;overflow:hidden;clip:rect(0,0,0,0);border:0}.sr-only-focusable:active,.sr-only-focusable:focus{position:static;width:auto;height:auto;margin:0;overflow:visible;clip:auto}[role=button]{cursor:pointer}.h1,.h2,.h3,.h4,.h5,.h6,h1,h2,h3,h4,h5,h6{font-family:inherit;font-weight:500;line-height:1.1;color:inherit}.h1 .small,.h1 small,.h2 .small,.h2 small,.h3 .small,.h3 small,.h4 .small,.h4 small,.h5 .small,.h5 small,.h6 .small,.h6 small,h1 .small,h1 small,h2 .small,h2 small,h3 .small,h3 small,h4 .small,h4 small,h5 .small,h5 small,h6 .small,h6 small{font-weight:400;line-height:1;color:#777}.h1,.h2,.h3,h1,h2,h3{margin-top:20px;margin-bottom:10px}.h1 .small,.h1 small,.h2 .small,.h2 small,.h3 .small,.h3 small,h1 .small,h1 small,h2 .small,h2 small,h3 .small,h3 small{font-size:65%}.h4,.h5,.h6,h4,h5,h6{margin-top:10px;margin-bottom:10px}.h4 .small,.h4 small,.h5 .small,.h5 small,.h6 .small,.h6 small,h4 .small,h4 small,h5 .small,h5 small,h6 .small,h6 small{font-size:75%}.h1,h1{font-size:36px}.h2,h2{font-size:30px}.h3,h3{font-size:24px}.h4,h4{font-size:18px}.h5,h5{font-size:14px}.h6,h6{font-size:12px}p{margin:0 0 10px}.lead{margin-bottom:20px;font-size:16px;font-weight:300;line-height:1.4}@media (min-width:768px){.lead{font-size:21px}}.small,small{font-size:85%}.mark,mark{padding:.2em;background-color:#fcf8e3}.text-left{text-align:left}.text-right{text-align:right}.text-center{text-align:center}.text-justify{text-align:justify}.text-nowrap{white-space:nowrap}.text-lowercase{text-transform:lowercase}.text-uppercase{text-transform:uppercase}.text-capitalize{text-transform:capitalize}.text-muted{color:#777}.text-primary{color:#337ab7}a.text-primary:focus,a.text-primary:hover{color:#286090}.text-success{color:#3c763d}a.text-success:focus,a.text-success:hover{color:#2b542c}.text-info{color:#31708f}a.text-info:focus,a.text-info:hover{color:#245269}.text-warning{color:#8a6d3b}a.text-warning:focus,a.text-warning:hover{color:#66512c}.text-danger{color:#a94442}a.text-danger:focus,a.text-danger:hover{color:#843534}.bg-primary{color:#fff;background-color:#337ab7}a.bg-primary:focus,a.bg-primary:hover{background-color:#286090}.bg-success{background-color:#dff0d8}a.bg-success:focus,a.bg-success:hover{background-color:#c1e2b3}.bg-info{background-color:#d9edf7}a.bg-info:focus,a.bg-info:hover{background-color:#afd9ee}.bg-warning{background-color:#fcf8e3}a.bg-warning:focus,a.bg-warning:hover{background-color:#f7ecb5}.bg-danger{background-color:#f2dede}a.bg-danger:focus,a.bg-danger:hover{background-color:#e4b9b9}.page-header{padding-bottom:9px;margin:40px 0 20px;border-bottom:1px solid #eee}ol,ul{margin-top:0;margin-bottom:10px}ol ol,ol ul,ul ol,ul ul{margin-bottom:0}.list-unstyled{padding-left:0;list-style:none}.list-inline{padding-left:0;margin-left:-5px;list-style:none}.list-inline>li{display:inline-block;padding-right:5px;padding-left:5px}dl{margin-top:0;margin-bottom:20px}dd,dt{line-height:1.42857143}dt{font-weight:700}dd{margin-left:0}@media (min-width:768px){.dl-horizontal dt{float:left;width:160px;overflow:hidden;clear:left;text-align:right;text-overflow:ellipsis;white-space:nowrap}.dl-horizontal dd{margin-left:180px}}abbr[data-original-title],abbr[title]{cursor:help;border-bottom:1px dotted #777}.initialism{font-size:90%;text-transform:uppercase}blockquote{padding:10px 20px;margin:0 0 20px;font-size:17.5px;border-left:5px solid #eee}blockquote ol:last-child,blockquote p:last-child,blockquote ul:last-child{margin-bottom:0}blockquote .small,blockquote footer,blockquote small{display:block;font-size:80%;line-height:1.42857143;color:#777}blockquote .small:before,blockquote footer:before,blockquote small:before{content:'\2014 \00A0'}.blockquote-reverse,blockquote.pull-right{padding-right:15px;padding-left:0;text-align:right;border-right:5px solid #eee;border-left:0}.blockquote-reverse .small:before,.blockquote-reverse footer:before,.blockquote-reverse small:before,blockquote.pull-right .small:before,blockquote.pull-right footer:before,blockquote.pull-right small:before{content:''}.blockquote-reverse .small:after,.blockquote-reverse footer:after,.blockquote-reverse small:after,blockquote.pull-right .small:after,blockquote.pull-right footer:after,blockquote.pull-right small:after{content:'\00A0 \2014'}address{margin-bottom:20px;font-style:normal;line-height:1.42857143}code,kbd,pre,samp{font-family:Menlo,Monaco,Consolas,"Courier New",monospace}code{padding:2px 4px;font-size:90%;color:#c7254e;background-color:#f9f2f4;border-radius:4px}kbd{padding:2px 4px;font-size:90%;color:#fff;background-color:#333;border-radius:3px;-webkit-box-shadow:inset 0 -1px 0 rgba(0,0,0,.25);box-shadow:inset 0 -1px 0 rgba(0,0,0,.25)}kbd kbd{padding:0;font-size:100%;font-weight:700;-webkit-box-shadow:none;box-shadow:none}pre{display:block;padding:9.5px;margin:0 0 10px;font-size:13px;line-height:1.42857143;color:#333;word-break:break-all;word-wrap:break-word;background-color:#f5f5f5;border:1px solid #ccc;border-radius:4px}pre code{padding:0;font-size:inherit;color:inherit;white-space:pre-wrap;background-color:transparent;border-radius:0}.pre-scrollable{max-height:340px;overflow-y:scroll}.container,.container-fluid{padding-right:15px;padding-left:15px;margin-right:auto;margin-left:auto}@media (min-width:768px){.container{width:750px}}@media (min-width:992px){.container{width:970px}}@media (min-width:1200px){.container{width:1170px}}.row{margin-right:-15px;margin-left:-15px}.col-lg-1,.col-lg-10,.col-lg-11,.col-lg-12,.col-lg-2,.col-lg-3,.col-lg-4,.col-lg-5,.col-lg-6,.col-lg-7,.col-lg-8,.col-lg-9,.col-md-1,.col-md-10,.col-md-11,.col-md-12,.col-md-2,.col-md-3,.col-md-4,.col-md-5,.col-md-6,.col-md-7,.col-md-8,.col-md-9,.col-sm-1,.col-sm-10,.col-sm-11,.col-sm-12,.col-sm-2,.col-sm-3,.col-sm-4,.col-sm-5,.col-sm-6,.col-sm-7,.col-sm-8,.col-sm-9,.col-xs-1,.col-xs-10,.col-xs-11,.col-xs-12,.col-xs-2,.col-xs-3,.col-xs-4,.col-xs-5,.col-xs-6,.col-xs-7,.col-xs-8,.col-xs-9{position:relative;min-height:1px;padding-right:15px;padding-left:15px}.col-xs-1,.col-xs-10,.col-xs-11,.col-xs-12,.col-xs-2,.col-xs-3,.col-xs-4,.col-xs-5,.col-xs-6,.col-xs-7,.col-xs-8,.col-xs-9{float:left}.col-xs-12{width:100%}.col-xs-11{width:91.66666667%}.col-xs-10{width:83.33333333%}.col-xs-9{width:75%}.col-xs-8{width:66.66666667%}.col-xs-7{width:58.33333333%}.col-xs-6{width:50%}.col-xs-5{width:41.66666667%}.col-xs-4{width:33.33333333%}.col-xs-3{width:25%}.col-xs-2{width:16.66666667%}.col-xs-1{width:8.33333333%}.col-xs-pull-12{right:100%}.col-xs-pull-11{right:91.66666667%}.col-xs-pull-10{right:83.33333333%}.col-xs-pull-9{right:75%}.col-xs-pull-8{right:66.66666667%}.col-xs-pull-7{right:58.33333333%}.col-xs-pull-6{right:50%}.col-xs-pull-5{right:41.66666667%}.col-xs-pull-4{right:33.33333333%}.col-xs-pull-3{right:25%}.col-xs-pull-2{right:16.66666667%}.col-xs-pull-1{right:8.33333333%}.col-xs-pull-0{right:auto}.col-xs-push-12{left:100%}.col-xs-push-11{left:91.66666667%}.col-xs-push-10{left:83.33333333%}.col-xs-push-9{left:75%}.col-xs-push-8{left:66.66666667%}.col-xs-push-7{left:58.33333333%}.col-xs-push-6{left:50%}.col-xs-push-5{left:41.66666667%}.col-xs-push-4{left:33.33333333%}.col-xs-push-3{left:25%}.col-xs-push-2{left:16.66666667%}.col-xs-push-1{left:8.33333333%}.col-xs-push-0{left:auto}.col-xs-offset-12{margin-left:100%}.col-xs-offset-11{margin-left:91.66666667%}.col-xs-offset-10{margin-left:83.33333333%}.col-xs-offset-9{margin-left:75%}.col-xs-offset-8{margin-left:66.66666667%}.col-xs-offset-7{margin-left:58.33333333%}.col-xs-offset-6{margin-left:50%}.col-xs-offset-5{margin-left:41.66666667%}.col-xs-offset-4{margin-left:33.33333333%}.col-xs-offset-3{margin-left:25%}.col-xs-offset-2{margin-left:16.66666667%}.col-xs-offset-1{margin-left:8.33333333%}.col-xs-offset-0{margin-left:0}@media (min-width:768px){.col-sm-1,.col-sm-10,.col-sm-11,.col-sm-12,.col-sm-2,.col-sm-3,.col-sm-4,.col-sm-5,.col-sm-6,.col-sm-7,.col-sm-8,.col-sm-9{float:left}.col-sm-12{width:100%}.col-sm-11{width:91.66666667%}.col-sm-10{width:83.33333333%}.col-sm-9{width:75%}.col-sm-8{width:66.66666667%}.col-sm-7{width:58.33333333%}.col-sm-6{width:50%}.col-sm-5{width:41.66666667%}.col-sm-4{width:33.33333333%}.col-sm-3{width:25%}.col-sm-2{width:16.66666667%}.col-sm-1{width:8.33333333%}.col-sm-pull-12{right:100%}.col-sm-pull-11{right:91.66666667%}.col-sm-pull-10{right:83.33333333%}.col-sm-pull-9{right:75%}.col-sm-pull-8{right:66.66666667%}.col-sm-pull-7{right:58.33333333%}.col-sm-pull-6{right:50%}.col-sm-pull-5{right:41.66666667%}.col-sm-pull-4{right:33.33333333%}.col-sm-pull-3{right:25%}.col-sm-pull-2{right:16.66666667%}.col-sm-pull-1{right:8.33333333%}.col-sm-pull-0{right:auto}.col-sm-push-12{left:100%}.col-sm-push-11{left:91.66666667%}.col-sm-push-10{left:83.33333333%}.col-sm-push-9{left:75%}.col-sm-push-8{left:66.66666667%}.col-sm-push-7{left:58.33333333%}.col-sm-push-6{left:50%}.col-sm-push-5{left:41.66666667%}.col-sm-push-4{left:33.33333333%}.col-sm-push-3{left:25%}.col-sm-push-2{left:16.66666667%}.col-sm-push-1{left:8.33333333%}.col-sm-push-0{left:auto}.col-sm-offset-12{margin-left:100%}.col-sm-offset-11{margin-left:91.66666667%}.col-sm-offset-10{margin-left:83.33333333%}.col-sm-offset-9{margin-left:75%}.col-sm-offset-8{margin-left:66.66666667%}.col-sm-offset-7{margin-left:58.33333333%}.col-sm-offset-6{margin-left:50%}.col-sm-offset-5{margin-left:41.66666667%}.col-sm-offset-4{margin-left:33.33333333%}.col-sm-offset-3{margin-left:25%}.col-sm-offset-2{margin-left:16.66666667%}.col-sm-offset-1{margin-left:8.33333333%}.col-sm-offset-0{margin-left:0}}@media (min-width:992px){.col-md-1,.col-md-10,.col-md-11,.col-md-12,.col-md-2,.col-md-3,.col-md-4,.col-md-5,.col-md-6,.col-md-7,.col-md-8,.col-md-9{float:left}.col-md-12{width:100%}.col-md-11{width:91.66666667%}.col-md-10{width:83.33333333%}.col-md-9{width:75%}.col-md-8{width:66.66666667%}.col-md-7{width:58.33333333%}.col-md-6{width:50%}.col-md-5{width:41.66666667%}.col-md-4{width:33.33333333%}.col-md-3{width:25%}.col-md-2{width:16.66666667%}.col-md-1{width:8.33333333%}.col-md-pull-12{right:100%}.col-md-pull-11{right:91.66666667%}.col-md-pull-10{right:83.33333333%}.col-md-pull-9{right:75%}.col-md-pull-8{right:66.66666667%}.col-md-pull-7{right:58.33333333%}.col-md-pull-6{right:50%}.col-md-pull-5{right:41.66666667%}.col-md-pull-4{right:33.33333333%}.col-md-pull-3{right:25%}.col-md-pull-2{right:16.66666667%}.col-md-pull-1{right:8.33333333%}.col-md-pull-0{right:auto}.col-md-push-12{left:100%}.col-md-push-11{left:91.66666667%}.col-md-push-10{left:83.33333333%}.col-md-push-9{left:75%}.col-md-push-8{left:66.66666667%}.col-md-push-7{left:58.33333333%}.col-md-push-6{left:50%}.col-md-push-5{left:41.66666667%}.col-md-push-4{left:33.33333333%}.col-md-push-3{left:25%}.col-md-push-2{left:16.66666667%}.col-md-push-1{left:8.33333333%}.col-md-push-0{left:auto}.col-md-offset-12{margin-left:100%}.col-md-offset-11{margin-left:91.66666667%}.col-md-offset-10{margin-left:83.33333333%}.col-md-offset-9{margin-left:75%}.col-md-offset-8{margin-left:66.66666667%}.col-md-offset-7{margin-left:58.33333333%}.col-md-offset-6{margin-left:50%}.col-md-offset-5{margin-left:41.66666667%}.col-md-offset-4{margin-left:33.33333333%}.col-md-offset-3{margin-left:25%}.col-md-offset-2{margin-left:16.66666667%}.col-md-offset-1{margin-left:8.33333333%}.col-md-offset-0{margin-left:0}}@media (min-width:1200px){.col-lg-1,.col-lg-10,.col-lg-11,.col-lg-12,.col-lg-2,.col-lg-3,.col-lg-4,.col-lg-5,.col-lg-6,.col-lg-7,.col-lg-8,.col-lg-9{float:left}.col-lg-12{width:100%}.col-lg-11{width:91.66666667%}.col-lg-10{width:83.33333333%}.col-lg-9{width:75%}.col-lg-8{width:66.66666667%}.col-lg-7{width:58.33333333%}.col-lg-6{width:50%}.col-lg-5{width:41.66666667%}.col-lg-4{width:33.33333333%}.col-lg-3{width:25%}.col-lg-2{width:16.66666667%}.col-lg-1{width:8.33333333%}.col-lg-pull-12{right:100%}.col-lg-pull-11{right:91.66666667%}.col-lg-pull-10{right:83.33333333%}.col-lg-pull-9{right:75%}.col-lg-pull-8{right:66.66666667%}.col-lg-pull-7{right:58.33333333%}.col-lg-pull-6{right:50%}.col-lg-pull-5{right:41.66666667%}.col-lg-pull-4{right:33.33333333%}.col-lg-pull-3{right:25%}.col-lg-pull-2{right:16.66666667%}.col-lg-pull-1{right:8.33333333%}.col-lg-pull-0{right:auto}.col-lg-push-12{left:100%}.col-lg-push-11{left:91.66666667%}.col-lg-push-10{left:83.33333333%}.col-lg-push-9{left:75%}.col-lg-push-8{left:66.66666667%}.col-lg-push-7{left:58.33333333%}.col-lg-push-6{left:50%}.col-lg-push-5{left:41.66666667%}.col-lg-push-4{left:33.33333333%}.col-lg-push-3{left:25%}.col-lg-push-2{left:16.66666667%}.col-lg-push-1{left:8.33333333%}.col-lg-push-0{left:auto}.col-lg-offset-12{margin-left:100%}.col-lg-offset-11{margin-left:91.66666667%}.col-lg-offset-10{margin-left:83.33333333%}.col-lg-offset-9{margin-left:75%}.col-lg-offset-8{margin-left:66.66666667%}.col-lg-offset-7{margin-left:58.33333333%}.col-lg-offset-6{margin-left:50%}.col-lg-offset-5{margin-left:41.66666667%}.col-lg-offset-4{margin-left:33.33333333%}.col-lg-offset-3{margin-left:25%}.col-lg-offset-2{margin-left:16.66666667%}.col-lg-offset-1{margin-left:8.33333333%}.col-lg-offset-0{margin-left:0}}table{background-color:transparent}caption{padding-top:8px;padding-bottom:8px;color:#777;text-align:left}th{text-align:left}.table{width:100%;max-width:100%;margin-bottom:20px}.table>tbody>tr>td,.table>tbody>tr>th,.table>tfoot>tr>td,.table>tfoot>tr>th,.table>thead>tr>td,.table>thead>tr>th{padding:8px;line-height:1.42857143;vertical-align:top;border-top:1px solid #ddd}.table>thead>tr>th{vertical-align:bottom;border-bottom:2px solid #ddd}.table>caption+thead>tr:first-child>td,.table>caption+thead>tr:first-child>th,.table>colgroup+thead>tr:first-child>td,.table>colgroup+thead>tr:first-child>th,.table>thead:first-child>tr:first-child>td,.table>thead:first-child>tr:first-child>th{border-top:0}.table>tbody+tbody{border-top:2px solid #ddd}.table .table{background-color:#fff}.table-condensed>tbody>tr>td,.table-condensed>tbody>tr>th,.table-condensed>tfoot>tr>td,.table-condensed>tfoot>tr>th,.table-condensed>thead>tr>td,.table-condensed>thead>tr>th{padding:5px}.table-bordered,.table-bordered>tbody>tr>td,.table-bordered>tbody>tr>th,.table-bordered>tfoot>tr>td,.table-bordered>tfoot>tr>th,.table-bordered>thead>tr>td,.table-bordered>thead>tr>th{border:1px solid #ddd}.table-bordered>thead>tr>td,.table-bordered>thead>tr>th{border-bottom-width:2px}.table-striped>tbody>tr:nth-of-type(odd){background-color:#f9f9f9}.table-hover>tbody>tr:hover{background-color:#f5f5f5}table col[class*=col-]{position:static;display:table-column;float:none}table td[class*=col-],table th[class*=col-]{position:static;display:table-cell;float:none}.table>tbody>tr.active>td,.table>tbody>tr.active>th,.table>tbody>tr>td.active,.table>tbody>tr>th.active,.table>tfoot>tr.active>td,.table>tfoot>tr.active>th,.table>tfoot>tr>td.active,.table>tfoot>tr>th.active,.table>thead>tr.active>td,.table>thead>tr.active>th,.table>thead>tr>td.active,.table>thead>tr>th.active{background-color:#f5f5f5}.table-hover>tbody>tr.active:hover>td,.table-hover>tbody>tr.active:hover>th,.table-hover>tbody>tr:hover>.active,.table-hover>tbody>tr>td.active:hover,.table-hover>tbody>tr>th.active:hover{background-color:#e8e8e8}.table>tbody>tr.success>td,.table>tbody>tr.success>th,.table>tbody>tr>td.success,.table>tbody>tr>th.success,.table>tfoot>tr.success>td,.table>tfoot>tr.success>th,.table>tfoot>tr>td.success,.table>tfoot>tr>th.success,.table>thead>tr.success>td,.table>thead>tr.success>th,.table>thead>tr>td.success,.table>thead>tr>th.success{background-color:#dff0d8}.table-hover>tbody>tr.success:hover>td,.table-hover>tbody>tr.success:hover>th,.table-hover>tbody>tr:hover>.success,.table-hover>tbody>tr>td.success:hover,.table-hover>tbody>tr>th.success:hover{background-color:#d0e9c6}.table>tbody>tr.info>td,.table>tbody>tr.info>th,.table>tbody>tr>td.info,.table>tbody>tr>th.info,.table>tfoot>tr.info>td,.table>tfoot>tr.info>th,.table>tfoot>tr>td.info,.table>tfoot>tr>th.info,.table>thead>tr.info>td,.table>thead>tr.info>th,.table>thead>tr>td.info,.table>thead>tr>th.info{background-color:#d9edf7}.table-hover>tbody>tr.info:hover>td,.table-hover>tbody>tr.info:hover>th,.table-hover>tbody>tr:hover>.info,.table-hover>tbody>tr>td.info:hover,.table-hover>tbody>tr>th.info:hover{background-color:#c4e3f3}.table>tbody>tr.warning>td,.table>tbody>tr.warning>th,.table>tbody>tr>td.warning,.table>tbody>tr>th.warning,.table>tfoot>tr.warning>td,.table>tfoot>tr.warning>th,.table>tfoot>tr>td.warning,.table>tfoot>tr>th.warning,.table>thead>tr.warning>td,.table>thead>tr.warning>th,.table>thead>tr>td.warning,.table>thead>tr>th.warning{background-color:#fcf8e3}.table-hover>tbody>tr.warning:hover>td,.table-hover>tbody>tr.warning:hover>th,.table-hover>tbody>tr:hover>.warning,.table-hover>tbody>tr>td.warning:hover,.table-hover>tbody>tr>th.warning:hover{background-color:#faf2cc}.table>tbody>tr.danger>td,.table>tbody>tr.danger>th,.table>tbody>tr>td.danger,.table>tbody>tr>th.danger,.table>tfoot>tr.danger>td,.table>tfoot>tr.danger>th,.table>tfoot>tr>td.danger,.table>tfoot>tr>th.danger,.table>thead>tr.danger>td,.table>thead>tr.danger>th,.table>thead>tr>td.danger,.table>thead>tr>th.danger{background-color:#f2dede}.table-hover>tbody>tr.danger:hover>td,.table-hover>tbody>tr.danger:hover>th,.table-hover>tbody>tr:hover>.danger,.table-hover>tbody>tr>td.danger:hover,.table-hover>tbody>tr>th.danger:hover{background-color:#ebcccc}.table-responsive{min-height:.01%;overflow-x:auto}@media screen and (max-width:767px){.table-responsive{width:100%;margin-bottom:15px;overflow-y:hidden;-ms-overflow-style:-ms-autohiding-scrollbar;border:1px solid #ddd}.table-responsive>.table{margin-bottom:0}.table-responsive>.table>tbody>tr>td,.table-responsive>.table>tbody>tr>th,.table-responsive>.table>tfoot>tr>td,.table-responsive>.table>tfoot>tr>th,.table-responsive>.table>thead>tr>td,.table-responsive>.table>thead>tr>th{white-space:nowrap}.table-responsive>.table-bordered{border:0}.table-responsive>.table-bordered>tbody>tr>td:first-child,.table-responsive>.table-bordered>tbody>tr>th:first-child,.table-responsive>.table-bordered>tfoot>tr>td:first-child,.table-responsive>.table-bordered>tfoot>tr>th:first-child,.table-responsive>.table-bordered>thead>tr>td:first-child,.table-responsive>.table-bordered>thead>tr>th:first-child{border-left:0}.table-responsive>.table-bordered>tbody>tr>td:last-child,.table-responsive>.table-bordered>tbody>tr>th:last-child,.table-responsive>.table-bordered>tfoot>tr>td:last-child,.table-responsive>.table-bordered>tfoot>tr>th:last-child,.table-responsive>.table-bordered>thead>tr>td:last-child,.table-responsive>.table-bordered>thead>tr>th:last-child{border-right:0}.table-responsive>.table-bordered>tbody>tr:last-child>td,.table-responsive>.table-bordered>tbody>tr:last-child>th,.table-responsive>.table-bordered>tfoot>tr:last-child>td,.table-responsive>.table-bordered>tfoot>tr:last-child>th{border-bottom:0}}fieldset{min-width:0;padding:0;margin:0;border:0}legend{display:block;width:100%;padding:0;margin-bottom:20px;font-size:21px;line-height:inherit;color:#333;border:0;border-bottom:1px solid #e5e5e5}label{display:inline-block;max-width:100%;margin-bottom:5px;font-weight:700}input[type=search]{-webkit-box-sizing:border-box;-moz-box-sizing:border-box;box-sizing:border-box}input[type=checkbox],input[type=radio]{margin:4px 0 0;line-height:normal}input[type=file]{display:block}input[type=range]{display:block;width:100%}select[multiple],select[size]{height:auto}input[type=checkbox]:focus,input[type=file]:focus,input[type=radio]:focus{outline:-webkit-focus-ring-color auto 5px;outline-offset:-2px}output{display:block;padding-top:7px;font-size:14px;line-height:1.42857143;color:#555}.form-control{display:block;width:100%;height:34px;padding:6px 12px;font-size:14px;line-height:1.42857143;color:#555;background-color:#fff;background-image:none;border:1px solid #ccc;border-radius:4px;-webkit-box-shadow:inset 0 1px 1px rgba(0,0,0,.075);box-shadow:inset 0 1px 1px rgba(0,0,0,.075);-webkit-transition:border-color ease-in-out .15s,-webkit-box-shadow ease-in-out .15s;-o-transition:border-color ease-in-out .15s,box-shadow ease-in-out .15s;transition:border-color ease-in-out .15s,box-shadow ease-in-out .15s}.form-control:focus{border-color:#66afe9;outline:0;-webkit-box-shadow:inset 0 1px 1px rgba(0,0,0,.075),0 0 8px rgba(102,175,233,.6);box-shadow:inset 0 1px 1px rgba(0,0,0,.075),0 0 8px rgba(102,175,233,.6)}.form-control::-moz-placeholder{color:#999;opacity:1}.form-control:-ms-input-placeholder{color:#999}.form-control::-webkit-input-placeholder{color:#999}.form-control::-ms-expand{background-color:transparent;border:0}.form-control[disabled],.form-control[readonly],fieldset[disabled] .form-control{background-color:#eee;opacity:1}.form-control[disabled],fieldset[disabled] .form-control{cursor:not-allowed}textarea.form-control{height:auto}input[type=search]{-webkit-appearance:none}@media screen and (-webkit-min-device-pixel-ratio:0){input[type=date].form-control,input[type=datetime-local].form-control,input[type=month].form-control,input[type=time].form-control{line-height:34px}.input-group-sm input[type=date],.input-group-sm input[type=datetime-local],.input-group-sm input[type=month],.input-group-sm input[type=time],input[type=date].input-sm,input[type=datetime-local].input-sm,input[type=month].input-sm,input[type=time].input-sm{line-height:30px}.input-group-lg input[type=date],.input-group-lg input[type=datetime-local],.input-group-lg input[type=month],.input-group-lg input[type=time],input[type=date].input-lg,input[type=datetime-local].input-lg,input[type=month].input-lg,input[type=time].input-lg{line-height:46px}}.form-group{margin-bottom:15px}.checkbox,.radio{position:relative;display:block;margin-top:10px;margin-bottom:10px}.checkbox label,.radio label{min-height:20px;padding-left:20px;margin-bottom:0;font-weight:400;cursor:pointer}.checkbox input[type=checkbox],.checkbox-inline input[type=checkbox],.radio input[type=radio],.radio-inline input[type=radio]{position:absolute;margin-left:-20px}.checkbox+.checkbox,.radio+.radio{margin-top:-5px}.checkbox-inline,.radio-inline{position:relative;display:inline-block;padding-left:20px;margin-bottom:0;font-weight:400;vertical-align:middle;cursor:pointer}.checkbox-inline+.checkbox-inline,.radio-inline+.radio-inline{margin-top:0;margin-left:10px}.checkbox-inline.disabled,.checkbox.disabled label,.radio-inline.disabled,.radio.disabled label,fieldset[disabled] .checkbox label,fieldset[disabled] .checkbox-inline,fieldset[disabled] .radio label,fieldset[disabled] .radio-inline,fieldset[disabled] input[type=checkbox],fieldset[disabled] input[type=radio],input[type=checkbox].disabled,input[type=checkbox][disabled],input[type=radio].disabled,input[type=radio][disabled]{cursor:not-allowed}.form-control-static{min-height:34px;padding-top:7px;padding-bottom:7px;margin-bottom:0}.form-control-static.input-lg,.form-control-static.input-sm{padding-right:0;padding-left:0}.input-sm{height:30px;padding:5px 10px;font-size:12px;line-height:1.5;border-radius:3px}select.input-sm{height:30px;line-height:30px}select[multiple].input-sm,textarea.input-sm{height:auto}.form-group-sm .form-control{height:30px;padding:5px 10px;font-size:12px;line-height:1.5;border-radius:3px}.form-group-sm select.form-control{height:30px;line-height:30px}.form-group-sm select[multiple].form-control,.form-group-sm textarea.form-control{height:auto}.form-group-sm .form-control-static{height:30px;min-height:32px;padding:6px 10px;font-size:12px;line-height:1.5}.input-lg{height:46px;padding:10px 16px;font-size:18px;line-height:1.3333333;border-radius:6px}select.input-lg{height:46px;line-height:46px}select[multiple].input-lg,textarea.input-lg{height:auto}.form-group-lg .form-control{height:46px;padding:10px 16px;font-size:18px;line-height:1.3333333;border-radius:6px}.form-group-lg select.form-control{height:46px;line-height:46px}.form-group-lg select[multiple].form-control,.form-group-lg textarea.form-control{height:auto}.form-group-lg .form-control-static{height:46px;min-height:38px;padding:11px 16px;font-size:18px;line-height:1.3333333}.has-feedback{position:relative}.has-feedback .form-control{padding-right:42.5px}.form-control-feedback{position:absolute;top:0;right:0;z-index:2;display:block;width:34px;height:34px;line-height:34px;text-align:center;pointer-events:none}.form-group-lg .form-control+.form-control-feedback,.input-group-lg+.form-control-feedback,.input-lg+.form-control-feedback{width:46px;height:46px;line-height:46px}.form-group-sm .form-control+.form-control-feedback,.input-group-sm+.form-control-feedback,.input-sm+.form-control-feedback{width:30px;height:30px;line-height:30px}.has-success .checkbox,.has-success .checkbox-inline,.has-success .control-label,.has-success .help-block,.has-success .radio,.has-success .radio-inline,.has-success.checkbox label,.has-success.checkbox-inline label,.has-success.radio label,.has-success.radio-inline label{color:#3c763d}.has-success .form-control{border-color:#3c763d;-webkit-box-shadow:inset 0 1px 1px rgba(0,0,0,.075);box-shadow:inset 0 1px 1px rgba(0,0,0,.075)}.has-success .form-control:focus{border-color:#2b542c;-webkit-box-shadow:inset 0 1px 1px rgba(0,0,0,.075),0 0 6px #67b168;box-shadow:inset 0 1px 1px rgba(0,0,0,.075),0 0 6px #67b168}.has-success .input-group-addon{color:#3c763d;background-color:#dff0d8;border-color:#3c763d}.has-success .form-control-feedback{color:#3c763d}.has-warning .checkbox,.has-warning .checkbox-inline,.has-warning .control-label,.has-warning .help-block,.has-warning .radio,.has-warning .radio-inline,.has-warning.checkbox label,.has-warning.checkbox-inline label,.has-warning.radio label,.has-warning.radio-inline label{color:#8a6d3b}.has-warning .form-control{border-color:#8a6d3b;-webkit-box-shadow:inset 0 1px 1px rgba(0,0,0,.075);box-shadow:inset 0 1px 1px rgba(0,0,0,.075)}.has-warning .form-control:focus{border-color:#66512c;-webkit-box-shadow:inset 0 1px 1px rgba(0,0,0,.075),0 0 6px #c0a16b;box-shadow:inset 0 1px 1px rgba(0,0,0,.075),0 0 6px #c0a16b}.has-warning .input-group-addon{color:#8a6d3b;background-color:#fcf8e3;border-color:#8a6d3b}.has-warning .form-control-feedback{color:#8a6d3b}.has-error .checkbox,.has-error .checkbox-inline,.has-error .control-label,.has-error .help-block,.has-error .radio,.has-error .radio-inline,.has-error.checkbox label,.has-error.checkbox-inline label,.has-error.radio label,.has-error.radio-inline label{color:#a94442}.has-error .form-control{border-color:#a94442;-webkit-box-shadow:inset 0 1px 1px rgba(0,0,0,.075);box-shadow:inset 0 1px 1px rgba(0,0,0,.075)}.has-error .form-control:focus{border-color:#843534;-webkit-box-shadow:inset 0 1px 1px rgba(0,0,0,.075),0 0 6px #ce8483;box-shadow:inset 0 1px 1px rgba(0,0,0,.075),0 0 6px #ce8483}.has-error .input-group-addon{color:#a94442;background-color:#f2dede;border-color:#a94442}.has-error .form-control-feedback{color:#a94442}.has-feedback label~.form-control-feedback{top:25px}.has-feedback label.sr-only~.form-control-feedback{top:0}.help-block{display:block;margin-top:5px;margin-bottom:10px;color:#737373}@media (min-width:768px){.form-inline .form-group{display:inline-block;margin-bottom:0;vertical-align:middle}.form-inline .form-control{display:inline-block;width:auto;vertical-align:middle}.form-inline .form-control-static{display:inline-block}.form-inline .input-group{display:inline-table;vertical-align:middle}.form-inline .input-group .form-control,.form-inline .input-group .input-group-addon,.form-inline .input-group .input-group-btn{width:auto}.form-inline .input-group>.form-control{width:100%}.form-inline .control-label{margin-bottom:0;vertical-align:middle}.form-inline .checkbox,.form-inline .radio{display:inline-block;margin-top:0;margin-bottom:0;vertical-align:middle}.form-inline .checkbox label,.form-inline .radio label{padding-left:0}.form-inline .checkbox input[type=checkbox],.form-inline .radio input[type=radio]{position:relative;margin-left:0}.form-inline .has-feedback .form-control-feedback{top:0}}.form-horizontal .checkbox,.form-horizontal .checkbox-inline,.form-horizontal .radio,.form-horizontal .radio-inline{padding-top:7px;margin-top:0;margin-bottom:0}.form-horizontal .checkbox,.form-horizontal .radio{min-height:27px}.form-horizontal .form-group{margin-right:-15px;margin-left:-15px}@media (min-width:768px){.form-horizontal .control-label{padding-top:7px;margin-bottom:0;text-align:right}}.form-horizontal .has-feedback .form-control-feedback{right:15px}@media (min-width:768px){.form-horizontal .form-group-lg .control-label{padding-top:11px;font-size:18px}}@media (min-width:768px){.form-horizontal .form-group-sm .control-label{padding-top:6px;font-size:12px}}.btn{display:inline-block;padding:6px 12px;margin-bottom:0;font-size:14px;font-weight:400;line-height:1.42857143;text-align:center;white-space:nowrap;vertical-align:middle;-ms-touch-action:manipulation;touch-action:manipulation;cursor:pointer;-webkit-user-select:none;-moz-user-select:none;-ms-user-select:none;user-select:none;background-image:none;border:1px solid transparent;border-radius:4px}.btn.active.focus,.btn.active:focus,.btn.focus,.btn:active.focus,.btn:active:focus,.btn:focus{outline:-webkit-focus-ring-color auto 5px;outline-offset:-2px}.btn.focus,.btn:focus,.btn:hover{color:#333;text-decoration:none}.btn.active,.btn:active{background-image:none;outline:0;-webkit-box-shadow:inset 0 3px 5px rgba(0,0,0,.125);box-shadow:inset 0 3px 5px rgba(0,0,0,.125)}.btn.disabled,.btn[disabled],fieldset[disabled] .btn{cursor:not-allowed;filter:alpha(opacity=65);-webkit-box-shadow:none;box-shadow:none;opacity:.65}a.btn.disabled,fieldset[disabled] a.btn{pointer-events:none}.btn-default{color:#333;background-color:#fff;border-color:#ccc}.btn-default.focus,.btn-default:focus{color:#333;background-color:#e6e6e6;border-color:#8c8c8c}.btn-default.active,.btn-default:active,.btn-default:hover,.open>.dropdown-toggle.btn-default{color:#333;background-color:#e6e6e6;border-color:#adadad}.btn-default.active.focus,.btn-default.active:focus,.btn-default.active:hover,.btn-default:active.focus,.btn-default:active:focus,.btn-default:active:hover,.open>.dropdown-toggle.btn-default.focus,.open>.dropdown-toggle.btn-default:focus,.open>.dropdown-toggle.btn-default:hover{color:#333;background-color:#d4d4d4;border-color:#8c8c8c}.btn-default.active,.btn-default:active,.open>.dropdown-toggle.btn-default{background-image:none}.btn-default.disabled.focus,.btn-default.disabled:focus,.btn-default.disabled:hover,.btn-default[disabled].focus,.btn-default[disabled]:focus,.btn-default[disabled]:hover,fieldset[disabled] .btn-default.focus,fieldset[disabled] .btn-default:focus,fieldset[disabled] .btn-default:hover{background-color:#fff;border-color:#ccc}.btn-default .badge{color:#fff;background-color:#333}.btn-primary{color:#fff;background-color:#337ab7;border-color:#2e6da4}.btn-primary.focus,.btn-primary:focus{color:#fff;background-color:#286090;border-color:#122b40}.btn-primary.active,.btn-primary:active,.btn-primary:hover,.open>.dropdown-toggle.btn-primary{color:#fff;background-color:#286090;border-color:#204d74}.btn-primary.active.focus,.btn-primary.active:focus,.btn-primary.active:hover,.btn-primary:active.focus,.btn-primary:active:focus,.btn-primary:active:hover,.open>.dropdown-toggle.btn-primary.focus,.open>.dropdown-toggle.btn-primary:focus,.open>.dropdown-toggle.btn-primary:hover{color:#fff;background-color:#204d74;border-color:#122b40}.btn-primary.active,.btn-primary:active,.open>.dropdown-toggle.btn-primary{background-image:none}.btn-primary.disabled.focus,.btn-primary.disabled:focus,.btn-primary.disabled:hover,.btn-primary[disabled].focus,.btn-primary[disabled]:focus,.btn-primary[disabled]:hover,fieldset[disabled] .btn-primary.focus,fieldset[disabled] .btn-primary:focus,fieldset[disabled] .btn-primary:hover{background-color:#337ab7;border-color:#2e6da4}.btn-primary .badge{color:#337ab7;background-color:#fff}.btn-success{color:#fff;background-color:#5cb85c;border-color:#4cae4c}.btn-success.focus,.btn-success:focus{color:#fff;background-color:#449d44;border-color:#255625}.btn-success.active,.btn-success:active,.btn-success:hover,.open>.dropdown-toggle.btn-success{color:#fff;background-color:#449d44;border-color:#398439}.btn-success.active.focus,.btn-success.active:focus,.btn-success.active:hover,.btn-success:active.focus,.btn-success:active:focus,.btn-success:active:hover,.open>.dropdown-toggle.btn-success.focus,.open>.dropdown-toggle.btn-success:focus,.open>.dropdown-toggle.btn-success:hover{color:#fff;background-color:#398439;border-color:#255625}.btn-success.active,.btn-success:active,.open>.dropdown-toggle.btn-success{background-image:none}.btn-success.disabled.focus,.btn-success.disabled:focus,.btn-success.disabled:hover,.btn-success[disabled].focus,.btn-success[disabled]:focus,.btn-success[disabled]:hover,fieldset[disabled] .btn-success.focus,fieldset[disabled] .btn-success:focus,fieldset[disabled] .btn-success:hover{background-color:#5cb85c;border-color:#4cae4c}.btn-success .badge{color:#5cb85c;background-color:#fff}.btn-info{color:#fff;background-color:#5bc0de;border-color:#46b8da}.btn-info.focus,.btn-info:focus{color:#fff;background-color:#31b0d5;border-color:#1b6d85}.btn-info.active,.btn-info:active,.btn-info:hover,.open>.dropdown-toggle.btn-info{color:#fff;background-color:#31b0d5;border-color:#269abc}.btn-info.active.focus,.btn-info.active:focus,.btn-info.active:hover,.btn-info:active.focus,.btn-info:active:focus,.btn-info:active:hover,.open>.dropdown-toggle.btn-info.focus,.open>.dropdown-toggle.btn-info:focus,.open>.dropdown-toggle.btn-info:hover{color:#fff;background-color:#269abc;border-color:#1b6d85}.btn-info.active,.btn-info:active,.open>.dropdown-toggle.btn-info{background-image:none}.btn-info.disabled.focus,.btn-info.disabled:focus,.btn-info.disabled:hover,.btn-info[disabled].focus,.btn-info[disabled]:focus,.btn-info[disabled]:hover,fieldset[disabled] .btn-info.focus,fieldset[disabled] .btn-info:focus,fieldset[disabled] .btn-info:hover{background-color:#5bc0de;border-color:#46b8da}.btn-info .badge{color:#5bc0de;background-color:#fff}.btn-warning{color:#fff;background-color:#f0ad4e;border-color:#eea236}.btn-warning.focus,.btn-warning:focus{color:#fff;background-color:#ec971f;border-color:#985f0d}.btn-warning.active,.btn-warning:active,.btn-warning:hover,.open>.dropdown-toggle.btn-warning{color:#fff;background-color:#ec971f;border-color:#d58512}.btn-warning.active.focus,.btn-warning.active:focus,.btn-warning.active:hover,.btn-warning:active.focus,.btn-warning:active:focus,.btn-warning:active:hover,.open>.dropdown-toggle.btn-warning.focus,.open>.dropdown-toggle.btn-warning:focus,.open>.dropdown-toggle.btn-warning:hover{color:#fff;background-color:#d58512;border-color:#985f0d}.btn-warning.active,.btn-warning:active,.open>.dropdown-toggle.btn-warning{background-image:none}.btn-warning.disabled.focus,.btn-warning.disabled:focus,.btn-warning.disabled:hover,.btn-warning[disabled].focus,.btn-warning[disabled]:focus,.btn-warning[disabled]:hover,fieldset[disabled] .btn-warning.focus,fieldset[disabled] .btn-warning:focus,fieldset[disabled] .btn-warning:hover{background-color:#f0ad4e;border-color:#eea236}.btn-warning .badge{color:#f0ad4e;background-color:#fff}.btn-danger{color:#fff;background-color:#d9534f;border-color:#d43f3a}.btn-danger.focus,.btn-danger:focus{color:#fff;background-color:#c9302c;border-color:#761c19}.btn-danger.active,.btn-danger:active,.btn-danger:hover,.open>.dropdown-toggle.btn-danger{color:#fff;background-color:#c9302c;border-color:#ac2925}.btn-danger.active.focus,.btn-danger.active:focus,.btn-danger.active:hover,.btn-danger:active.focus,.btn-danger:active:focus,.btn-danger:active:hover,.open>.dropdown-toggle.btn-danger.focus,.open>.dropdown-toggle.btn-danger:focus,.open>.dropdown-toggle.btn-danger:hover{color:#fff;background-color:#ac2925;border-color:#761c19}.btn-danger.active,.btn-danger:active,.open>.dropdown-toggle.btn-danger{background-image:none}.btn-danger.disabled.focus,.btn-danger.disabled:focus,.btn-danger.disabled:hover,.btn-danger[disabled].focus,.btn-danger[disabled]:focus,.btn-danger[disabled]:hover,fieldset[disabled] .btn-danger.focus,fieldset[disabled] .btn-danger:focus,fieldset[disabled] .btn-danger:hover{background-color:#d9534f;border-color:#d43f3a}.btn-danger .badge{color:#d9534f;background-color:#fff}.btn-link{font-weight:400;color:#337ab7;border-radius:0}.btn-link,.btn-link.active,.btn-link:active,.btn-link[disabled],fieldset[disabled] .btn-link{background-color:transparent;-webkit-box-shadow:none;box-shadow:none}.btn-link,.btn-link:active,.btn-link:focus,.btn-link:hover{border-color:transparent}.btn-link:focus,.btn-link:hover{color:#23527c;text-decoration:underline;background-color:transparent}.btn-link[disabled]:focus,.btn-link[disabled]:hover,fieldset[disabled] .btn-link:focus,fieldset[disabled] .btn-link:hover{color:#777;text-decoration:none}.btn-group-lg>.btn,.btn-lg{padding:10px 16px;font-size:18px;line-height:1.3333333;border-radius:6px}.btn-group-sm>.btn,.btn-sm{padding:5px 10px;font-size:12px;line-height:1.5;border-radius:3px}.btn-group-xs>.btn,.btn-xs{padding:1px 5px;font-size:12px;line-height:1.5;border-radius:3px}.btn-block{display:block;width:100%}.btn-block+.btn-block{margin-top:5px}input[type=button].btn-block,input[type=reset].btn-block,input[type=submit].btn-block{width:100%}.fade{opacity:0;-webkit-transition:opacity .15s linear;-o-transition:opacity .15s linear;transition:opacity .15s linear}.fade.in{opacity:1}.collapse{display:none}.collapse.in{display:block}tr.collapse.in{display:table-row}tbody.collapse.in{display:table-row-group}.collapsing{position:relative;height:0;overflow:hidden;-webkit-transition-timing-function:ease;-o-transition-timing-function:ease;transition-timing-function:ease;-webkit-transition-duration:.35s;-o-transition-duration:.35s;transition-duration:.35s;-webkit-transition-property:height,visibility;-o-transition-property:height,visibility;transition-property:height,visibility}.caret{display:inline-block;width:0;height:0;margin-left:2px;vertical-align:middle;border-top:4px dashed;border-right:4px solid transparent;border-left:4px solid transparent}.dropdown,.dropup{position:relative}.dropdown-toggle:focus{outline:0}.dropdown-menu{position:absolute;top:100%;left:0;z-index:1000;display:none;float:left;min-width:160px;padding:5px 0;margin:2px 0 0;font-size:14px;text-align:left;list-style:none;background-color:#fff;-webkit-background-clip:padding-box;background-clip:padding-box;border:1px solid #ccc;border:1px solid rgba(0,0,0,.15);border-radius:4px;-webkit-box-shadow:0 6px 12px rgba(0,0,0,.175);box-shadow:0 6px 12px rgba(0,0,0,.175)}.dropdown-menu.pull-right{right:0;left:auto}.dropdown-menu .divider{height:1px;margin:9px 0;overflow:hidden;background-color:#e5e5e5}.dropdown-menu>li>a{display:block;padding:3px 20px;clear:both;font-weight:400;line-height:1.42857143;color:#333;white-space:nowrap}.dropdown-menu>li>a:focus,.dropdown-menu>li>a:hover{color:#262626;text-decoration:none;background-color:#f5f5f5}.dropdown-menu>.active>a,.dropdown-menu>.active>a:focus,.dropdown-menu>.active>a:hover{color:#fff;text-decoration:none;background-color:#337ab7;outline:0}.dropdown-menu>.disabled>a,.dropdown-menu>.disabled>a:focus,.dropdown-menu>.disabled>a:hover{color:#777}.dropdown-menu>.disabled>a:focus,.dropdown-menu>.disabled>a:hover{text-decoration:none;cursor:not-allowed;background-color:transparent;background-image:none;filter:progid:DXImageTransform.Microsoft.gradient(enabled=false)}.open>.dropdown-menu{display:block}.open>a{outline:0}.dropdown-menu-right{right:0;left:auto}.dropdown-menu-left{right:auto;left:0}.dropdown-header{display:block;padding:3px 20px;font-size:12px;line-height:1.42857143;color:#777;white-space:nowrap}.dropdown-backdrop{position:fixed;top:0;right:0;bottom:0;left:0;z-index:990}.pull-right>.dropdown-menu{right:0;left:auto}.dropup .caret,.navbar-fixed-bottom .dropdown .caret{content:"";border-top:0;border-bottom:4px dashed}.dropup .dropdown-menu,.navbar-fixed-bottom .dropdown .dropdown-menu{top:auto;bottom:100%;margin-bottom:2px}@media (min-width:768px){.navbar-right .dropdown-menu{right:0;left:auto}.navbar-right .dropdown-menu-left{right:auto;left:0}}.btn-group,.btn-group-vertical{position:relative;display:inline-block;vertical-align:middle}.btn-group-vertical>.btn,.btn-group>.btn{position:relative;float:left}.btn-group-vertical>.btn.active,.btn-group-vertical>.btn:active,.btn-group-vertical>.btn:focus,.btn-group-vertical>.btn:hover,.btn-group>.btn.active,.btn-group>.btn:active,.btn-group>.btn:focus,.btn-group>.btn:hover{z-index:2}.btn-group .btn+.btn,.btn-group .btn+.btn-group,.btn-group .btn-group+.btn,.btn-group .btn-group+.btn-group{margin-left:-1px}.btn-toolbar{margin-left:-5px}.btn-toolbar .btn,.btn-toolbar .btn-group,.btn-toolbar .input-group{float:left}.btn-toolbar>.btn,.btn-toolbar>.btn-group,.btn-toolbar>.input-group{margin-left:5px}.btn-group>.btn:not(:first-child):not(:last-child):not(.dropdown-toggle){border-radius:0}.btn-group>.btn:first-child{margin-left:0}.btn-group>.btn:first-child:not(:last-child):not(.dropdown-toggle){border-top-right-radius:0;border-bottom-right-radius:0}.btn-group>.btn:last-child:not(:first-child),.btn-group>.dropdown-toggle:not(:first-child){border-top-left-radius:0;border-bottom-left-radius:0}.btn-group>.btn-group{float:left}.btn-group>.btn-group:not(:first-child):not(:last-child)>.btn{border-radius:0}.btn-group>.btn-group:first-child:not(:last-child)>.btn:last-child,.btn-group>.btn-group:first-child:not(:last-child)>.dropdown-toggle{border-top-right-radius:0;border-bottom-right-radius:0}.btn-group>.btn-group:last-child:not(:first-child)>.btn:first-child{border-top-left-radius:0;border-bottom-left-radius:0}.btn-group .dropdown-toggle:active,.btn-group.open .dropdown-toggle{outline:0}.btn-group>.btn+.dropdown-toggle{padding-right:8px;padding-left:8px}.btn-group>.btn-lg+.dropdown-toggle{padding-right:12px;padding-left:12px}.btn-group.open .dropdown-toggle{-webkit-box-shadow:inset 0 3px 5px rgba(0,0,0,.125);box-shadow:inset 0 3px 5px rgba(0,0,0,.125)}.btn-group.open .dropdown-toggle.btn-link{-webkit-box-shadow:none;box-shadow:none}.btn .caret{margin-left:0}.btn-lg .caret{border-width:5px 5px 0}.dropup .btn-lg .caret{border-width:0 5px 5px}.btn-group-vertical>.btn,.btn-group-vertical>.btn-group,.btn-group-vertical>.btn-group>.btn{display:block;float:none;width:100%;max-width:100%}.btn-group-vertical>.btn-group>.btn{float:none}.btn-group-vertical>.btn+.btn,.btn-group-vertical>.btn+.btn-group,.btn-group-vertical>.btn-group+.btn,.btn-group-vertical>.btn-group+.btn-group{margin-top:-1px;margin-left:0}.btn-group-vertical>.btn:not(:first-child):not(:last-child){border-radius:0}.btn-group-vertical>.btn:first-child:not(:last-child){border-radius:4px 4px 0 0}.btn-group-vertical>.btn:last-child:not(:first-child){border-radius:0 0 4px 4px}.btn-group-vertical>.btn-group:not(:first-child):not(:last-child)>.btn{border-radius:0}.btn-group-vertical>.btn-group:first-child:not(:last-child)>.btn:last-child,.btn-group-vertical>.btn-group:first-child:not(:last-child)>.dropdown-toggle{border-bottom-right-radius:0;border-bottom-left-radius:0}.btn-group-vertical>.btn-group:last-child:not(:first-child)>.btn:first-child{border-top-left-radius:0;border-top-right-radius:0}.btn-group-justified{display:table;width:100%;table-layout:fixed;border-collapse:separate}.btn-group-justified>.btn,.btn-group-justified>.btn-group{display:table-cell;float:none;width:1%}.btn-group-justified>.btn-group .btn{width:100%}.btn-group-justified>.btn-group .dropdown-menu{left:auto}[data-toggle=buttons]>.btn input[type=checkbox],[data-toggle=buttons]>.btn input[type=radio],[data-toggle=buttons]>.btn-group>.btn input[type=checkbox],[data-toggle=buttons]>.btn-group>.btn input[type=radio]{position:absolute;clip:rect(0,0,0,0);pointer-events:none}.input-group{position:relative;display:table;border-collapse:separate}.input-group[class*=col-]{float:none;padding-right:0;padding-left:0}.input-group .form-control{position:relative;z-index:2;float:left;width:100%;margin-bottom:0}.input-group .form-control:focus{z-index:3}.input-group-lg>.form-control,.input-group-lg>.input-group-addon,.input-group-lg>.input-group-btn>.btn{height:46px;padding:10px 16px;font-size:18px;line-height:1.3333333;border-radius:6px}select.input-group-lg>.form-control,select.input-group-lg>.input-group-addon,select.input-group-lg>.input-group-btn>.btn{height:46px;line-height:46px}select[multiple].input-group-lg>.form-control,select[multiple].input-group-lg>.input-group-addon,select[multiple].input-group-lg>.input-group-btn>.btn,textarea.input-group-lg>.form-control,textarea.input-group-lg>.input-group-addon,textarea.input-group-lg>.input-group-btn>.btn{height:auto}.input-group-sm>.form-control,.input-group-sm>.input-group-addon,.input-group-sm>.input-group-btn>.btn{height:30px;padding:5px 10px;font-size:12px;line-height:1.5;border-radius:3px}select.input-group-sm>.form-control,select.input-group-sm>.input-group-addon,select.input-group-sm>.input-group-btn>.btn{height:30px;line-height:30px}select[multiple].input-group-sm>.form-control,select[multiple].input-group-sm>.input-group-addon,select[multiple].input-group-sm>.input-group-btn>.btn,textarea.input-group-sm>.form-control,textarea.input-group-sm>.input-group-addon,textarea.input-group-sm>.input-group-btn>.btn{height:auto}.input-group .form-control,.input-group-addon,.input-group-btn{display:table-cell}.input-group .form-control:not(:first-child):not(:last-child),.input-group-addon:not(:first-child):not(:last-child),.input-group-btn:not(:first-child):not(:last-child){border-radius:0}.input-group-addon,.input-group-btn{width:1%;white-space:nowrap;vertical-align:middle}.input-group-addon{padding:6px 12px;font-size:14px;font-weight:400;line-height:1;color:#555;text-align:center;background-color:#eee;border:1px solid #ccc;border-radius:4px}.input-group-addon.input-sm{padding:5px 10px;font-size:12px;border-radius:3px}.input-group-addon.input-lg{padding:10px 16px;font-size:18px;border-radius:6px}.input-group-addon input[type=checkbox],.input-group-addon input[type=radio]{margin-top:0}.input-group .form-control:first-child,.input-group-addon:first-child,.input-group-btn:first-child>.btn,.input-group-btn:first-child>.btn-group>.btn,.input-group-btn:first-child>.dropdown-toggle,.input-group-btn:last-child>.btn-group:not(:last-child)>.btn,.input-group-btn:last-child>.btn:not(:last-child):not(.dropdown-toggle){border-top-right-radius:0;border-bottom-right-radius:0}.input-group-addon:first-child{border-right:0}.input-group .form-control:last-child,.input-group-addon:last-child,.input-group-btn:first-child>.btn-group:not(:first-child)>.btn,.input-group-btn:first-child>.btn:not(:first-child),.input-group-btn:last-child>.btn,.input-group-btn:last-child>.btn-group>.btn,.input-group-btn:last-child>.dropdown-toggle{border-top-left-radius:0;border-bottom-left-radius:0}.input-group-addon:last-child{border-left:0}.input-group-btn{position:relative;font-size:0;white-space:nowrap}.input-group-btn>.btn{position:relative}.input-group-btn>.btn+.btn{margin-left:-1px}.input-group-btn>.btn:active,.input-group-btn>.btn:focus,.input-group-btn>.btn:hover{z-index:2}.input-group-btn:first-child>.btn,.input-group-btn:first-child>.btn-group{margin-right:-1px}.input-group-btn:last-child>.btn,.input-group-btn:last-child>.btn-group{z-index:2;margin-left:-1px}.nav{padding-left:0;margin-bottom:0;list-style:none}.nav>li{position:relative;display:block}.nav>li>a{position:relative;display:block;padding:10px 15px}.nav>li>a:focus,.nav>li>a:hover{text-decoration:none;background-color:#eee}.nav>li.disabled>a{color:#777}.nav>li.disabled>a:focus,.nav>li.disabled>a:hover{color:#777;text-decoration:none;cursor:not-allowed;background-color:transparent}.nav .open>a,.nav .open>a:focus,.nav .open>a:hover{background-color:#eee;border-color:#337ab7}.nav .nav-divider{height:1px;margin:9px 0;overflow:hidden;background-color:#e5e5e5}.nav>li>a>img{max-width:none}.nav-tabs{border-bottom:1px solid #ddd}.nav-tabs>li{float:left;margin-bottom:-1px}.nav-tabs>li>a{margin-right:2px;line-height:1.42857143;border:1px solid transparent;border-radius:4px 4px 0 0}.nav-tabs>li>a:hover{border-color:#eee #eee #ddd}.nav-tabs>li.active>a,.nav-tabs>li.active>a:focus,.nav-tabs>li.active>a:hover{color:#555;cursor:default;background-color:#fff;border:1px solid #ddd;border-bottom-color:transparent}.nav-tabs.nav-justified{width:100%;border-bottom:0}.nav-tabs.nav-justified>li{float:none}.nav-tabs.nav-justified>li>a{margin-bottom:5px;text-align:center}.nav-tabs.nav-justified>.dropdown .dropdown-menu{top:auto;left:auto}@media (min-width:768px){.nav-tabs.nav-justified>li{display:table-cell;width:1%}.nav-tabs.nav-justified>li>a{margin-bottom:0}}.nav-tabs.nav-justified>li>a{margin-right:0;border-radius:4px}.nav-tabs.nav-justified>.active>a,.nav-tabs.nav-justified>.active>a:focus,.nav-tabs.nav-justified>.active>a:hover{border:1px solid #ddd}@media (min-width:768px){.nav-tabs.nav-justified>li>a{border-bottom:1px solid #ddd;border-radius:4px 4px 0 0}.nav-tabs.nav-justified>.active>a,.nav-tabs.nav-justified>.active>a:focus,.nav-tabs.nav-justified>.active>a:hover{border-bottom-color:#fff}}.nav-pills>li{float:left}.nav-pills>li>a{border-radius:4px}.nav-pills>li+li{margin-left:2px}.nav-pills>li.active>a,.nav-pills>li.active>a:focus,.nav-pills>li.active>a:hover{color:#fff;background-color:#337ab7}.nav-stacked>li{float:none}.nav-stacked>li+li{margin-top:2px;margin-left:0}.nav-justified{width:100%}.nav-justified>li{float:none}.nav-justified>li>a{margin-bottom:5px;text-align:center}.nav-justified>.dropdown .dropdown-menu{top:auto;left:auto}@media (min-width:768px){.nav-justified>li{display:table-cell;width:1%}.nav-justified>li>a{margin-bottom:0}}.nav-tabs-justified{border-bottom:0}.nav-tabs-justified>li>a{margin-right:0;border-radius:4px}.nav-tabs-justified>.active>a,.nav-tabs-justified>.active>a:focus,.nav-tabs-justified>.active>a:hover{border:1px solid #ddd}@media (min-width:768px){.nav-tabs-justified>li>a{border-bottom:1px solid #ddd;border-radius:4px 4px 0 0}.nav-tabs-justified>.active>a,.nav-tabs-justified>.active>a:focus,.nav-tabs-justified>.active>a:hover{border-bottom-color:#fff}}.tab-content>.tab-pane{display:none}.tab-content>.active{display:block}.nav-tabs .dropdown-menu{margin-top:-1px;border-top-left-radius:0;border-top-right-radius:0}.navbar{position:relative;min-height:50px;margin-bottom:20px;border:1px solid transparent}@media (min-width:768px){.navbar{border-radius:4px}}@media (min-width:768px){.navbar-header{float:left}}.navbar-collapse{padding-right:15px;padding-left:15px;overflow-x:visible;-webkit-overflow-scrolling:touch;border-top:1px solid transparent;-webkit-box-shadow:inset 0 1px 0 rgba(255,255,255,.1);box-shadow:inset 0 1px 0 rgba(255,255,255,.1)}.navbar-collapse.in{overflow-y:auto}@media (min-width:768px){.navbar-collapse{width:auto;border-top:0;-webkit-box-shadow:none;box-shadow:none}.navbar-collapse.collapse{display:block!important;height:auto!important;padding-bottom:0;overflow:visible!important}.navbar-collapse.in{overflow-y:visible}.navbar-fixed-bottom .navbar-collapse,.navbar-fixed-top .navbar-collapse,.navbar-static-top .navbar-collapse{padding-right:0;padding-left:0}}.navbar-fixed-bottom .navbar-collapse,.navbar-fixed-top .navbar-collapse{max-height:340px}@media (max-device-width:480px) and (orientation:landscape){.navbar-fixed-bottom .navbar-collapse,.navbar-fixed-top .navbar-collapse{max-height:200px}}.container-fluid>.navbar-collapse,.container-fluid>.navbar-header,.container>.navbar-collapse,.container>.navbar-header{margin-right:-15px;margin-left:-15px}@media (min-width:768px){.container-fluid>.navbar-collapse,.container-fluid>.navbar-header,.container>.navbar-collapse,.container>.navbar-header{margin-right:0;margin-left:0}}.navbar-static-top{z-index:1000;border-width:0 0 1px}@media (min-width:768px){.navbar-static-top{border-radius:0}}.navbar-fixed-bottom,.navbar-fixed-top{position:fixed;right:0;left:0;z-index:1030}@media (min-width:768px){.navbar-fixed-bottom,.navbar-fixed-top{border-radius:0}}.navbar-fixed-top{top:0;border-width:0 0 1px}.navbar-fixed-bottom{bottom:0;margin-bottom:0;border-width:1px 0 0}.navbar-brand{float:left;height:50px;padding:15px;font-size:18px;line-height:20px}.navbar-brand:focus,.navbar-brand:hover{text-decoration:none}.navbar-brand>img{display:block}@media (min-width:768px){.navbar>.container .navbar-brand,.navbar>.container-fluid .navbar-brand{margin-left:-15px}}.navbar-toggle{position:relative;float:right;padding:9px 10px;margin-top:8px;margin-right:15px;margin-bottom:8px;background-color:transparent;background-image:none;border:1px solid transparent;border-radius:4px}.navbar-toggle:focus{outline:0}.navbar-toggle .icon-bar{display:block;width:22px;height:2px;border-radius:1px}.navbar-toggle .icon-bar+.icon-bar{margin-top:4px}@media (min-width:768px){.navbar-toggle{display:none}}.navbar-nav{margin:7.5px -15px}.navbar-nav>li>a{padding-top:10px;padding-bottom:10px;line-height:20px}@media (max-width:767px){.navbar-nav .open .dropdown-menu{position:static;float:none;width:auto;margin-top:0;background-color:transparent;border:0;-webkit-box-shadow:none;box-shadow:none}.navbar-nav .open .dropdown-menu .dropdown-header,.navbar-nav .open .dropdown-menu>li>a{padding:5px 15px 5px 25px}.navbar-nav .open .dropdown-menu>li>a{line-height:20px}.navbar-nav .open .dropdown-menu>li>a:focus,.navbar-nav .open .dropdown-menu>li>a:hover{background-image:none}}@media (min-width:768px){.navbar-nav{float:left;margin:0}.navbar-nav>li{float:left}.navbar-nav>li>a{padding-top:15px;padding-bottom:15px}}.navbar-form{padding:10px 15px;margin:8px -15px;border-top:1px solid transparent;border-bottom:1px solid transparent;-webkit-box-shadow:inset 0 1px 0 rgba(255,255,255,.1),0 1px 0 rgba(255,255,255,.1);box-shadow:inset 0 1px 0 rgba(255,255,255,.1),0 1px 0 rgba(255,255,255,.1)}@media (min-width:768px){.navbar-form .form-group{display:inline-block;margin-bottom:0;vertical-align:middle}.navbar-form .form-control{display:inline-block;width:auto;vertical-align:middle}.navbar-form .form-control-static{display:inline-block}.navbar-form .input-group{display:inline-table;vertical-align:middle}.navbar-form .input-group .form-control,.navbar-form .input-group .input-group-addon,.navbar-form .input-group .input-group-btn{width:auto}.navbar-form .input-group>.form-control{width:100%}.navbar-form .control-label{margin-bottom:0;vertical-align:middle}.navbar-form .checkbox,.navbar-form .radio{display:inline-block;margin-top:0;margin-bottom:0;vertical-align:middle}.navbar-form .checkbox label,.navbar-form .radio label{padding-left:0}.navbar-form .checkbox input[type=checkbox],.navbar-form .radio input[type=radio]{position:relative;margin-left:0}.navbar-form .has-feedback .form-control-feedback{top:0}}@media (max-width:767px){.navbar-form .form-group{margin-bottom:5px}.navbar-form .form-group:last-child{margin-bottom:0}}@media (min-width:768px){.navbar-form{width:auto;padding-top:0;padding-bottom:0;margin-right:0;margin-left:0;border:0;-webkit-box-shadow:none;box-shadow:none}}.navbar-nav>li>.dropdown-menu{margin-top:0;border-top-left-radius:0;border-top-right-radius:0}.navbar-fixed-bottom .navbar-nav>li>.dropdown-menu{margin-bottom:0;border-radius:4px 4px 0 0}.navbar-btn{margin-top:8px;margin-bottom:8px}.navbar-btn.btn-sm{margin-top:10px;margin-bottom:10px}.navbar-btn.btn-xs{margin-top:14px;margin-bottom:14px}.navbar-text{margin-top:15px;margin-bottom:15px}@media (min-width:768px){.navbar-text{float:left;margin-right:15px;margin-left:15px}}@media (min-width:768px){.navbar-left{float:left!important}.navbar-right{float:right!important;margin-right:-15px}.navbar-right~.navbar-right{margin-right:0}}.navbar-default{background-color:#f8f8f8;border-color:#e7e7e7}.navbar-default .navbar-brand{color:#777}.navbar-default .navbar-brand:focus,.navbar-default .navbar-brand:hover{color:#5e5e5e;background-color:transparent}.navbar-default .navbar-nav>li>a,.navbar-default .navbar-text{color:#777}.navbar-default .navbar-nav>li>a:focus,.navbar-default .navbar-nav>li>a:hover{color:#333;background-color:transparent}.navbar-default .navbar-nav>.active>a,.navbar-default .navbar-nav>.active>a:focus,.navbar-default .navbar-nav>.active>a:hover{color:#555;background-color:#e7e7e7}.navbar-default .navbar-nav>.disabled>a,.navbar-default .navbar-nav>.disabled>a:focus,.navbar-default .navbar-nav>.disabled>a:hover{color:#ccc;background-color:transparent}.navbar-default .navbar-toggle{border-color:#ddd}.navbar-default .navbar-toggle:focus,.navbar-default .navbar-toggle:hover{background-color:#ddd}.navbar-default .navbar-toggle .icon-bar{background-color:#888}.navbar-default .navbar-collapse,.navbar-default .navbar-form{border-color:#e7e7e7}.navbar-default .navbar-nav>.open>a,.navbar-default .navbar-nav>.open>a:focus,.navbar-default .navbar-nav>.open>a:hover{color:#555;background-color:#e7e7e7}@media (max-width:767px){.navbar-default .navbar-nav .open .dropdown-menu>li>a{color:#777}.navbar-default .navbar-nav .open .dropdown-menu>li>a:focus,.navbar-default .navbar-nav .open .dropdown-menu>li>a:hover{color:#333;background-color:transparent}.navbar-default .navbar-nav .open .dropdown-menu>.active>a,.navbar-default .navbar-nav .open .dropdown-menu>.active>a:focus,.navbar-default .navbar-nav .open .dropdown-menu>.active>a:hover{color:#555;background-color:#e7e7e7}.navbar-default .navbar-nav .open .dropdown-menu>.disabled>a,.navbar-default .navbar-nav .open .dropdown-menu>.disabled>a:focus,.navbar-default .navbar-nav .open .dropdown-menu>.disabled>a:hover{color:#ccc;background-color:transparent}}.navbar-default .navbar-link{color:#777}.navbar-default .navbar-link:hover{color:#333}.navbar-default .btn-link{color:#777}.navbar-default .btn-link:focus,.navbar-default .btn-link:hover{color:#333}.navbar-default .btn-link[disabled]:focus,.navbar-default .btn-link[disabled]:hover,fieldset[disabled] .navbar-default .btn-link:focus,fieldset[disabled] .navbar-default .btn-link:hover{color:#ccc}.navbar-inverse{background-color:#222;border-color:#080808}.navbar-inverse .navbar-brand{color:#9d9d9d}.navbar-inverse .navbar-brand:focus,.navbar-inverse .navbar-brand:hover{color:#fff;background-color:transparent}.navbar-inverse .navbar-nav>li>a,.navbar-inverse .navbar-text{color:#9d9d9d}.navbar-inverse .navbar-nav>li>a:focus,.navbar-inverse .navbar-nav>li>a:hover{color:#fff;background-color:transparent}.navbar-inverse .navbar-nav>.active>a,.navbar-inverse .navbar-nav>.active>a:focus,.navbar-inverse .navbar-nav>.active>a:hover{color:#fff;background-color:#080808}.navbar-inverse .navbar-nav>.disabled>a,.navbar-inverse .navbar-nav>.disabled>a:focus,.navbar-inverse .navbar-nav>.disabled>a:hover{color:#444;background-color:transparent}.navbar-inverse .navbar-toggle{border-color:#333}.navbar-inverse .navbar-toggle:focus,.navbar-inverse .navbar-toggle:hover{background-color:#333}.navbar-inverse .navbar-toggle .icon-bar{background-color:#fff}.navbar-inverse .navbar-collapse,.navbar-inverse .navbar-form{border-color:#101010}.navbar-inverse .navbar-nav>.open>a,.navbar-inverse .navbar-nav>.open>a:focus,.navbar-inverse .navbar-nav>.open>a:hover{color:#fff;background-color:#080808}@media (max-width:767px){.navbar-inverse .navbar-nav .open .dropdown-menu>.dropdown-header{border-color:#080808}.navbar-inverse .navbar-nav .open .dropdown-menu .divider{background-color:#080808}.navbar-inverse .navbar-nav .open .dropdown-menu>li>a{color:#9d9d9d}.navbar-inverse .navbar-nav .open .dropdown-menu>li>a:focus,.navbar-inverse .navbar-nav .open .dropdown-menu>li>a:hover{color:#fff;background-color:transparent}.navbar-inverse .navbar-nav .open .dropdown-menu>.active>a,.navbar-inverse .navbar-nav .open .dropdown-menu>.active>a:focus,.navbar-inverse .navbar-nav .open .dropdown-menu>.active>a:hover{color:#fff;background-color:#080808}.navbar-inverse .navbar-nav .open .dropdown-menu>.disabled>a,.navbar-inverse .navbar-nav .open .dropdown-menu>.disabled>a:focus,.navbar-inverse .navbar-nav .open .dropdown-menu>.disabled>a:hover{color:#444;background-color:transparent}}.navbar-inverse .navbar-link{color:#9d9d9d}.navbar-inverse .navbar-link:hover{color:#fff}.navbar-inverse .btn-link{color:#9d9d9d}.navbar-inverse .btn-link:focus,.navbar-inverse .btn-link:hover{color:#fff}.navbar-inverse .btn-link[disabled]:focus,.navbar-inverse .btn-link[disabled]:hover,fieldset[disabled] .navbar-inverse .btn-link:focus,fieldset[disabled] .navbar-inverse .btn-link:hover{color:#444}.breadcrumb{padding:8px 15px;margin-bottom:20px;list-style:none;background-color:#f5f5f5;border-radius:4px}.breadcrumb>li{display:inline-block}.breadcrumb>li+li:before{padding:0 5px;color:#ccc;content:"/\00a0"}.breadcrumb>.active{color:#777}.pagination{display:inline-block;padding-left:0;margin:20px 0;border-radius:4px}.pagination>li{display:inline}.pagination>li>a,.pagination>li>span{position:relative;float:left;padding:6px 12px;margin-left:-1px;line-height:1.42857143;color:#337ab7;text-decoration:none;background-color:#fff;border:1px solid #ddd}.pagination>li:first-child>a,.pagination>li:first-child>span{margin-left:0;border-top-left-radius:4px;border-bottom-left-radius:4px}.pagination>li:last-child>a,.pagination>li:last-child>span{border-top-right-radius:4px;border-bottom-right-radius:4px}.pagination>li>a:focus,.pagination>li>a:hover,.pagination>li>span:focus,.pagination>li>span:hover{z-index:2;color:#23527c;background-color:#eee;border-color:#ddd}.pagination>.active>a,.pagination>.active>a:focus,.pagination>.active>a:hover,.pagination>.active>span,.pagination>.active>span:focus,.pagination>.active>span:hover{z-index:3;color:#fff;cursor:default;background-color:#337ab7;border-color:#337ab7}.pagination>.disabled>a,.pagination>.disabled>a:focus,.pagination>.disabled>a:hover,.pagination>.disabled>span,.pagination>.disabled>span:focus,.pagination>.disabled>span:hover{color:#777;cursor:not-allowed;background-color:#fff;border-color:#ddd}.pagination-lg>li>a,.pagination-lg>li>span{padding:10px 16px;font-size:18px;line-height:1.3333333}.pagination-lg>li:first-child>a,.pagination-lg>li:first-child>span{border-top-left-radius:6px;border-bottom-left-radius:6px}.pagination-lg>li:last-child>a,.pagination-lg>li:last-child>span{border-top-right-radius:6px;border-bottom-right-radius:6px}.pagination-sm>li>a,.pagination-sm>li>span{padding:5px 10px;font-size:12px;line-height:1.5}.pagination-sm>li:first-child>a,.pagination-sm>li:first-child>span{border-top-left-radius:3px;border-bottom-left-radius:3px}.pagination-sm>li:last-child>a,.pagination-sm>li:last-child>span{border-top-right-radius:3px;border-bottom-right-radius:3px}.pager{padding-left:0;margin:20px 0;text-align:center;list-style:none}.pager li{display:inline}.pager li>a,.pager li>span{display:inline-block;padding:5px 14px;background-color:#fff;border:1px solid #ddd;border-radius:15px}.pager li>a:focus,.pager li>a:hover{text-decoration:none;background-color:#eee}.pager .next>a,.pager .next>span{float:right}.pager .previous>a,.pager .previous>span{float:left}.pager .disabled>a,.pager .disabled>a:focus,.pager .disabled>a:hover,.pager .disabled>span{color:#777;cursor:not-allowed;background-color:#fff}.label{display:inline;padding:.2em .6em .3em;font-size:75%;font-weight:700;line-height:1;color:#fff;text-align:center;white-space:nowrap;vertical-align:baseline;border-radius:.25em}a.label:focus,a.label:hover{color:#fff;text-decoration:none;cursor:pointer}.label:empty{display:none}.btn .label{position:relative;top:-1px}.label-default{background-color:#777}.label-default[href]:focus,.label-default[href]:hover{background-color:#5e5e5e}.label-primary{background-color:#337ab7}.label-primary[href]:focus,.label-primary[href]:hover{background-color:#286090}.label-success{background-color:#5cb85c}.label-success[href]:focus,.label-success[href]:hover{background-color:#449d44}.label-info{background-color:#5bc0de}.label-info[href]:focus,.label-info[href]:hover{background-color:#31b0d5}.label-warning{background-color:#f0ad4e}.label-warning[href]:focus,.label-warning[href]:hover{background-color:#ec971f}.label-danger{background-color:#d9534f}.label-danger[href]:focus,.label-danger[href]:hover{background-color:#c9302c}.badge{display:inline-block;min-width:10px;padding:3px 7px;font-size:12px;font-weight:700;line-height:1;color:#fff;text-align:center;white-space:nowrap;vertical-align:middle;background-color:#777;border-radius:10px}.badge:empty{display:none}.btn .badge{position:relative;top:-1px}.btn-group-xs>.btn .badge,.btn-xs .badge{top:0;padding:1px 5px}a.badge:focus,a.badge:hover{color:#fff;text-decoration:none;cursor:pointer}.list-group-item.active>.badge,.nav-pills>.active>a>.badge{color:#337ab7;background-color:#fff}.list-group-item>.badge{float:right}.list-group-item>.badge+.badge{margin-right:5px}.nav-pills>li>a>.badge{margin-left:3px}.jumbotron{padding-top:30px;padding-bottom:30px;margin-bottom:30px;color:inherit;background-color:#eee}.jumbotron .h1,.jumbotron h1{color:inherit}.jumbotron p{margin-bottom:15px;font-size:21px;font-weight:200}.jumbotron>hr{border-top-color:#d5d5d5}.container .jumbotron,.container-fluid .jumbotron{padding-right:15px;padding-left:15px;border-radius:6px}.jumbotron .container{max-width:100%}@media screen and (min-width:768px){.jumbotron{padding-top:48px;padding-bottom:48px}.container .jumbotron,.container-fluid .jumbotron{padding-right:60px;padding-left:60px}.jumbotron .h1,.jumbotron h1{font-size:63px}}.thumbnail{display:block;padding:4px;margin-bottom:20px;line-height:1.42857143;background-color:#fff;border:1px solid #ddd;border-radius:4px;-webkit-transition:border .2s ease-in-out;-o-transition:border .2s ease-in-out;transition:border .2s ease-in-out}.thumbnail a>img,.thumbnail>img{margin-right:auto;margin-left:auto}a.thumbnail.active,a.thumbnail:focus,a.thumbnail:hover{border-color:#337ab7}.thumbnail .caption{padding:9px;color:#333}.alert{padding:15px;margin-bottom:20px;border:1px solid transparent;border-radius:4px}.alert h4{margin-top:0;color:inherit}.alert .alert-link{font-weight:700}.alert>p,.alert>ul{margin-bottom:0}.alert>p+p{margin-top:5px}.alert-dismissable,.alert-dismissible{padding-right:35px}.alert-dismissable .close,.alert-dismissible .close{position:relative;top:-2px;right:-21px;color:inherit}.alert-success{color:#3c763d;background-color:#dff0d8;border-color:#d6e9c6}.alert-success hr{border-top-color:#c9e2b3}.alert-success .alert-link{color:#2b542c}.alert-info{color:#31708f;background-color:#d9edf7;border-color:#bce8f1}.alert-info hr{border-top-color:#a6e1ec}.alert-info .alert-link{color:#245269}.alert-warning{color:#8a6d3b;background-color:#fcf8e3;border-color:#faebcc}.alert-warning hr{border-top-color:#f7e1b5}.alert-warning .alert-link{color:#66512c}.alert-danger{color:#a94442;background-color:#f2dede;border-color:#ebccd1}.alert-danger hr{border-top-color:#e4b9c0}.alert-danger .alert-link{color:#843534}@-webkit-keyframes progress-bar-stripes{from{background-position:40px 0}to{background-position:0 0}}@-o-keyframes progress-bar-stripes{from{background-position:40px 0}to{background-position:0 0}}@keyframes progress-bar-stripes{from{background-position:40px 0}to{background-position:0 0}}.progress{height:20px;margin-bottom:20px;overflow:hidden;background-color:#f5f5f5;border-radius:4px;-webkit-box-shadow:inset 0 1px 2px rgba(0,0,0,.1);box-shadow:inset 0 1px 2px rgba(0,0,0,.1)}.progress-bar{float:left;width:0;height:100%;font-size:12px;line-height:20px;color:#fff;text-align:center;background-color:#337ab7;-webkit-box-shadow:inset 0 -1px 0 rgba(0,0,0,.15);box-shadow:inset 0 -1px 0 rgba(0,0,0,.15);-webkit-transition:width .6s ease;-o-transition:width .6s ease;transition:width .6s ease}.progress-bar-striped,.progress-striped .progress-bar{background-image:-webkit-linear-gradient(45deg,rgba(255,255,255,.15) 25%,transparent 25%,transparent 50%,rgba(255,255,255,.15) 50%,rgba(255,255,255,.15) 75%,transparent 75%,transparent);background-image:-o-linear-gradient(45deg,rgba(255,255,255,.15) 25%,transparent 25%,transparent 50%,rgba(255,255,255,.15) 50%,rgba(255,255,255,.15) 75%,transparent 75%,transparent);background-image:linear-gradient(45deg,rgba(255,255,255,.15) 25%,transparent 25%,transparent 50%,rgba(255,255,255,.15) 50%,rgba(255,255,255,.15) 75%,transparent 75%,transparent);-webkit-background-size:40px 40px;background-size:40px 40px}.progress-bar.active,.progress.active .progress-bar{-webkit-animation:progress-bar-stripes 2s linear infinite;-o-animation:progress-bar-stripes 2s linear infinite;animation:progress-bar-stripes 2s linear infinite}.progress-bar-success{background-color:#5cb85c}.progress-striped .progress-bar-success{background-image:-webkit-linear-gradient(45deg,rgba(255,255,255,.15) 25%,transparent 25%,transparent 50%,rgba(255,255,255,.15) 50%,rgba(255,255,255,.15) 75%,transparent 75%,transparent);background-image:-o-linear-gradient(45deg,rgba(255,255,255,.15) 25%,transparent 25%,transparent 50%,rgba(255,255,255,.15) 50%,rgba(255,255,255,.15) 75%,transparent 75%,transparent);background-image:linear-gradient(45deg,rgba(255,255,255,.15) 25%,transparent 25%,transparent 50%,rgba(255,255,255,.15) 50%,rgba(255,255,255,.15) 75%,transparent 75%,transparent)}.progress-bar-info{background-color:#5bc0de}.progress-striped .progress-bar-info{background-image:-webkit-linear-gradient(45deg,rgba(255,255,255,.15) 25%,transparent 25%,transparent 50%,rgba(255,255,255,.15) 50%,rgba(255,255,255,.15) 75%,transparent 75%,transparent);background-image:-o-linear-gradient(45deg,rgba(255,255,255,.15) 25%,transparent 25%,transparent 50%,rgba(255,255,255,.15) 50%,rgba(255,255,255,.15) 75%,transparent 75%,transparent);background-image:linear-gradient(45deg,rgba(255,255,255,.15) 25%,transparent 25%,transparent 50%,rgba(255,255,255,.15) 50%,rgba(255,255,255,.15) 75%,transparent 75%,transparent)}.progress-bar-warning{background-color:#f0ad4e}.progress-striped .progress-bar-warning{background-image:-webkit-linear-gradient(45deg,rgba(255,255,255,.15) 25%,transparent 25%,transparent 50%,rgba(255,255,255,.15) 50%,rgba(255,255,255,.15) 75%,transparent 75%,transparent);background-image:-o-linear-gradient(45deg,rgba(255,255,255,.15) 25%,transparent 25%,transparent 50%,rgba(255,255,255,.15) 50%,rgba(255,255,255,.15) 75%,transparent 75%,transparent);background-image:linear-gradient(45deg,rgba(255,255,255,.15) 25%,transparent 25%,transparent 50%,rgba(255,255,255,.15) 50%,rgba(255,255,255,.15) 75%,transparent 75%,transparent)}.progress-bar-danger{background-color:#d9534f}.progress-striped .progress-bar-danger{background-image:-webkit-linear-gradient(45deg,rgba(255,255,255,.15) 25%,transparent 25%,transparent 50%,rgba(255,255,255,.15) 50%,rgba(255,255,255,.15) 75%,transparent 75%,transparent);background-image:-o-linear-gradient(45deg,rgba(255,255,255,.15) 25%,transparent 25%,transparent 50%,rgba(255,255,255,.15) 50%,rgba(255,255,255,.15) 75%,transparent 75%,transparent);background-image:linear-gradient(45deg,rgba(255,255,255,.15) 25%,transparent 25%,transparent 50%,rgba(255,255,255,.15) 50%,rgba(255,255,255,.15) 75%,transparent 75%,transparent)}.media{margin-top:15px}.media:first-child{margin-top:0}.media,.media-body{overflow:hidden;zoom:1}.media-body{width:10000px}.media-object{display:block}.media-object.img-thumbnail{max-width:none}.media-right,.media>.pull-right{padding-left:10px}.media-left,.media>.pull-left{padding-right:10px}.media-body,.media-left,.media-right{display:table-cell;vertical-align:top}.media-middle{vertical-align:middle}.media-bottom{vertical-align:bottom}.media-heading{margin-top:0;margin-bottom:5px}.media-list{padding-left:0;list-style:none}.list-group{padding-left:0;margin-bottom:20px}.list-group-item{position:relative;display:block;padding:10px 15px;margin-bottom:-1px;background-color:#fff;border:1px solid #ddd}.list-group-item:first-child{border-top-left-radius:4px;border-top-right-radius:4px}.list-group-item:last-child{margin-bottom:0;border-bottom-right-radius:4px;border-bottom-left-radius:4px}a.list-group-item,button.list-group-item{color:#555}a.list-group-item .list-group-item-heading,button.list-group-item .list-group-item-heading{color:#333}a.list-group-item:focus,a.list-group-item:hover,button.list-group-item:focus,button.list-group-item:hover{color:#555;text-decoration:none;background-color:#f5f5f5}button.list-group-item{width:100%;text-align:left}.list-group-item.disabled,.list-group-item.disabled:focus,.list-group-item.disabled:hover{color:#777;cursor:not-allowed;background-color:#eee}.list-group-item.disabled .list-group-item-heading,.list-group-item.disabled:focus .list-group-item-heading,.list-group-item.disabled:hover .list-group-item-heading{color:inherit}.list-group-item.disabled .list-group-item-text,.list-group-item.disabled:focus .list-group-item-text,.list-group-item.disabled:hover .list-group-item-text{color:#777}.list-group-item.active,.list-group-item.active:focus,.list-group-item.active:hover{z-index:2;color:#fff;background-color:#337ab7;border-color:#337ab7}.list-group-item.active .list-group-item-heading,.list-group-item.active .list-group-item-heading>.small,.list-group-item.active .list-group-item-heading>small,.list-group-item.active:focus .list-group-item-heading,.list-group-item.active:focus .list-group-item-heading>.small,.list-group-item.active:focus .list-group-item-heading>small,.list-group-item.active:hover .list-group-item-heading,.list-group-item.active:hover .list-group-item-heading>.small,.list-group-item.active:hover .list-group-item-heading>small{color:inherit}.list-group-item.active .list-group-item-text,.list-group-item.active:focus .list-group-item-text,.list-group-item.active:hover .list-group-item-text{color:#c7ddef}.list-group-item-success{color:#3c763d;background-color:#dff0d8}a.list-group-item-success,button.list-group-item-success{color:#3c763d}a.list-group-item-success .list-group-item-heading,button.list-group-item-success .list-group-item-heading{color:inherit}a.list-group-item-success:focus,a.list-group-item-success:hover,button.list-group-item-success:focus,button.list-group-item-success:hover{color:#3c763d;background-color:#d0e9c6}a.list-group-item-success.active,a.list-group-item-success.active:focus,a.list-group-item-success.active:hover,button.list-group-item-success.active,button.list-group-item-success.active:focus,button.list-group-item-success.active:hover{color:#fff;background-color:#3c763d;border-color:#3c763d}.list-group-item-info{color:#31708f;background-color:#d9edf7}a.list-group-item-info,button.list-group-item-info{color:#31708f}a.list-group-item-info .list-group-item-heading,button.list-group-item-info .list-group-item-heading{color:inherit}a.list-group-item-info:focus,a.list-group-item-info:hover,button.list-group-item-info:focus,button.list-group-item-info:hover{color:#31708f;background-color:#c4e3f3}a.list-group-item-info.active,a.list-group-item-info.active:focus,a.list-group-item-info.active:hover,button.list-group-item-info.active,button.list-group-item-info.active:focus,button.list-group-item-info.active:hover{color:#fff;background-color:#31708f;border-color:#31708f}.list-group-item-warning{color:#8a6d3b;background-color:#fcf8e3}a.list-group-item-warning,button.list-group-item-warning{color:#8a6d3b}a.list-group-item-warning .list-group-item-heading,button.list-group-item-warning .list-group-item-heading{color:inherit}a.list-group-item-warning:focus,a.list-group-item-warning:hover,button.list-group-item-warning:focus,button.list-group-item-warning:hover{color:#8a6d3b;background-color:#faf2cc}a.list-group-item-warning.active,a.list-group-item-warning.active:focus,a.list-group-item-warning.active:hover,button.list-group-item-warning.active,button.list-group-item-warning.active:focus,button.list-group-item-warning.active:hover{color:#fff;background-color:#8a6d3b;border-color:#8a6d3b}.list-group-item-danger{color:#a94442;background-color:#f2dede}a.list-group-item-danger,button.list-group-item-danger{color:#a94442}a.list-group-item-danger .list-group-item-heading,button.list-group-item-danger .list-group-item-heading{color:inherit}a.list-group-item-danger:focus,a.list-group-item-danger:hover,button.list-group-item-danger:focus,button.list-group-item-danger:hover{color:#a94442;background-color:#ebcccc}a.list-group-item-danger.active,a.list-group-item-danger.active:focus,a.list-group-item-danger.active:hover,button.list-group-item-danger.active,button.list-group-item-danger.active:focus,button.list-group-item-danger.active:hover{color:#fff;background-color:#a94442;border-color:#a94442}.list-group-item-heading{margin-top:0;margin-bottom:5px}.list-group-item-text{margin-bottom:0;line-height:1.3}.panel{margin-bottom:20px;background-color:#fff;border:1px solid transparent;border-radius:4px;-webkit-box-shadow:0 1px 1px rgba(0,0,0,.05);box-shadow:0 1px 1px rgba(0,0,0,.05)}.panel-body{padding:15px}.panel-heading{padding:10px 15px;border-bottom:1px solid transparent;border-top-left-radius:3px;border-top-right-radius:3px}.panel-heading>.dropdown .dropdown-toggle{color:inherit}.panel-title{margin-top:0;margin-bottom:0;font-size:16px;color:inherit}.panel-title>.small,.panel-title>.small>a,.panel-title>a,.panel-title>small,.panel-title>small>a{color:inherit}.panel-footer{padding:10px 15px;background-color:#f5f5f5;border-top:1px solid #ddd;border-bottom-right-radius:3px;border-bottom-left-radius:3px}.panel>.list-group,.panel>.panel-collapse>.list-group{margin-bottom:0}.panel>.list-group .list-group-item,.panel>.panel-collapse>.list-group .list-group-item{border-width:1px 0;border-radius:0}.panel>.list-group:first-child .list-group-item:first-child,.panel>.panel-collapse>.list-group:first-child .list-group-item:first-child{border-top:0;border-top-left-radius:3px;border-top-right-radius:3px}.panel>.list-group:last-child .list-group-item:last-child,.panel>.panel-collapse>.list-group:last-child .list-group-item:last-child{border-bottom:0;border-bottom-right-radius:3px;border-bottom-left-radius:3px}.panel>.panel-heading+.panel-collapse>.list-group .list-group-item:first-child{border-top-left-radius:0;border-top-right-radius:0}.list-group+.panel-footer,.panel-heading+.list-group .list-group-item:first-child{border-top-width:0}.panel>.panel-collapse>.table,.panel>.table,.panel>.table-responsive>.table{margin-bottom:0}.panel>.panel-collapse>.table caption,.panel>.table caption,.panel>.table-responsive>.table caption{padding-right:15px;padding-left:15px}.panel>.table-responsive:first-child>.table:first-child,.panel>.table-responsive:first-child>.table:first-child>tbody:first-child>tr:first-child,.panel>.table-responsive:first-child>.table:first-child>thead:first-child>tr:first-child,.panel>.table:first-child,.panel>.table:first-child>tbody:first-child>tr:first-child,.panel>.table:first-child>thead:first-child>tr:first-child{border-top-left-radius:3px;border-top-right-radius:3px}.panel>.table-responsive:first-child>.table:first-child>tbody:first-child>tr:first-child td:first-child,.panel>.table-responsive:first-child>.table:first-child>tbody:first-child>tr:first-child th:first-child,.panel>.table-responsive:first-child>.table:first-child>thead:first-child>tr:first-child td:first-child,.panel>.table-responsive:first-child>.table:first-child>thead:first-child>tr:first-child th:first-child,.panel>.table:first-child>tbody:first-child>tr:first-child td:first-child,.panel>.table:first-child>tbody:first-child>tr:first-child th:first-child,.panel>.table:first-child>thead:first-child>tr:first-child td:first-child,.panel>.table:first-child>thead:first-child>tr:first-child th:first-child{border-top-left-radius:3px}.panel>.table-responsive:first-child>.table:first-child>tbody:first-child>tr:first-child td:last-child,.panel>.table-responsive:first-child>.table:first-child>tbody:first-child>tr:first-child th:last-child,.panel>.table-responsive:first-child>.table:first-child>thead:first-child>tr:first-child td:last-child,.panel>.table-responsive:first-child>.table:first-child>thead:first-child>tr:first-child th:last-child,.panel>.table:first-child>tbody:first-child>tr:first-child td:last-child,.panel>.table:first-child>tbody:first-child>tr:first-child th:last-child,.panel>.table:first-child>thead:first-child>tr:first-child td:last-child,.panel>.table:first-child>thead:first-child>tr:first-child th:last-child{border-top-right-radius:3px}.panel>.table-responsive:last-child>.table:last-child,.panel>.table-responsive:last-child>.table:last-child>tbody:last-child>tr:last-child,.panel>.table-responsive:last-child>.table:last-child>tfoot:last-child>tr:last-child,.panel>.table:last-child,.panel>.table:last-child>tbody:last-child>tr:last-child,.panel>.table:last-child>tfoot:last-child>tr:last-child{border-bottom-right-radius:3px;border-bottom-left-radius:3px}.panel>.table-responsive:last-child>.table:last-child>tbody:last-child>tr:last-child td:first-child,.panel>.table-responsive:last-child>.table:last-child>tbody:last-child>tr:last-child th:first-child,.panel>.table-responsive:last-child>.table:last-child>tfoot:last-child>tr:last-child td:first-child,.panel>.table-responsive:last-child>.table:last-child>tfoot:last-child>tr:last-child th:first-child,.panel>.table:last-child>tbody:last-child>tr:last-child td:first-child,.panel>.table:last-child>tbody:last-child>tr:last-child th:first-child,.panel>.table:last-child>tfoot:last-child>tr:last-child td:first-child,.panel>.table:last-child>tfoot:last-child>tr:last-child th:first-child{border-bottom-left-radius:3px}.panel>.table-responsive:last-child>.table:last-child>tbody:last-child>tr:last-child td:last-child,.panel>.table-responsive:last-child>.table:last-child>tbody:last-child>tr:last-child th:last-child,.panel>.table-responsive:last-child>.table:last-child>tfoot:last-child>tr:last-child td:last-child,.panel>.table-responsive:last-child>.table:last-child>tfoot:last-child>tr:last-child th:last-child,.panel>.table:last-child>tbody:last-child>tr:last-child td:last-child,.panel>.table:last-child>tbody:last-child>tr:last-child th:last-child,.panel>.table:last-child>tfoot:last-child>tr:last-child td:last-child,.panel>.table:last-child>tfoot:last-child>tr:last-child th:last-child{border-bottom-right-radius:3px}.panel>.panel-body+.table,.panel>.panel-body+.table-responsive,.panel>.table+.panel-body,.panel>.table-responsive+.panel-body{border-top:1px solid #ddd}.panel>.table>tbody:first-child>tr:first-child td,.panel>.table>tbody:first-child>tr:first-child th{border-top:0}.panel>.table-bordered,.panel>.table-responsive>.table-bordered{border:0}.panel>.table-bordered>tbody>tr>td:first-child,.panel>.table-bordered>tbody>tr>th:first-child,.panel>.table-bordered>tfoot>tr>td:first-child,.panel>.table-bordered>tfoot>tr>th:first-child,.panel>.table-bordered>thead>tr>td:first-child,.panel>.table-bordered>thead>tr>th:first-child,.panel>.table-responsive>.table-bordered>tbody>tr>td:first-child,.panel>.table-responsive>.table-bordered>tbody>tr>th:first-child,.panel>.table-responsive>.table-bordered>tfoot>tr>td:first-child,.panel>.table-responsive>.table-bordered>tfoot>tr>th:first-child,.panel>.table-responsive>.table-bordered>thead>tr>td:first-child,.panel>.table-responsive>.table-bordered>thead>tr>th:first-child{border-left:0}.panel>.table-bordered>tbody>tr>td:last-child,.panel>.table-bordered>tbody>tr>th:last-child,.panel>.table-bordered>tfoot>tr>td:last-child,.panel>.table-bordered>tfoot>tr>th:last-child,.panel>.table-bordered>thead>tr>td:last-child,.panel>.table-bordered>thead>tr>th:last-child,.panel>.table-responsive>.table-bordered>tbody>tr>td:last-child,.panel>.table-responsive>.table-bordered>tbody>tr>th:last-child,.panel>.table-responsive>.table-bordered>tfoot>tr>td:last-child,.panel>.table-responsive>.table-bordered>tfoot>tr>th:last-child,.panel>.table-responsive>.table-bordered>thead>tr>td:last-child,.panel>.table-responsive>.table-bordered>thead>tr>th:last-child{border-right:0}.panel>.table-bordered>tbody>tr:first-child>td,.panel>.table-bordered>tbody>tr:first-child>th,.panel>.table-bordered>tbody>tr:last-child>td,.panel>.table-bordered>tbody>tr:last-child>th,.panel>.table-bordered>tfoot>tr:last-child>td,.panel>.table-bordered>tfoot>tr:last-child>th,.panel>.table-bordered>thead>tr:first-child>td,.panel>.table-bordered>thead>tr:first-child>th,.panel>.table-responsive>.table-bordered>tbody>tr:first-child>td,.panel>.table-responsive>.table-bordered>tbody>tr:first-child>th,.panel>.table-responsive>.table-bordered>tbody>tr:last-child>td,.panel>.table-responsive>.table-bordered>tbody>tr:last-child>th,.panel>.table-responsive>.table-bordered>tfoot>tr:last-child>td,.panel>.table-responsive>.table-bordered>tfoot>tr:last-child>th,.panel>.table-responsive>.table-bordered>thead>tr:first-child>td,.panel>.table-responsive>.table-bordered>thead>tr:first-child>th{border-bottom:0}.panel>.table-responsive{margin-bottom:0;border:0}.panel-group{margin-bottom:20px}.panel-group .panel{margin-bottom:0;border-radius:4px}.panel-group .panel+.panel{margin-top:5px}.panel-group .panel-heading{border-bottom:0}.panel-group .panel-heading+.panel-collapse>.list-group,.panel-group .panel-heading+.panel-collapse>.panel-body{border-top:1px solid #ddd}.panel-group .panel-footer{border-top:0}.panel-group .panel-footer+.panel-collapse .panel-body{border-bottom:1px solid #ddd}.panel-default{border-color:#ddd}.panel-default>.panel-heading{color:#333;background-color:#f5f5f5;border-color:#ddd}.panel-default>.panel-heading+.panel-collapse>.panel-body{border-top-color:#ddd}.panel-default>.panel-heading .badge{color:#f5f5f5;background-color:#333}.panel-default>.panel-footer+.panel-collapse>.panel-body{border-bottom-color:#ddd}.panel-primary{border-color:#337ab7}.panel-primary>.panel-heading{color:#fff;background-color:#337ab7;border-color:#337ab7}.panel-primary>.panel-heading+.panel-collapse>.panel-body{border-top-color:#337ab7}.panel-primary>.panel-heading .badge{color:#337ab7;background-color:#fff}.panel-primary>.panel-footer+.panel-collapse>.panel-body{border-bottom-color:#337ab7}.panel-success{border-color:#d6e9c6}.panel-success>.panel-heading{color:#3c763d;background-color:#dff0d8;border-color:#d6e9c6}.panel-success>.panel-heading+.panel-collapse>.panel-body{border-top-color:#d6e9c6}.panel-success>.panel-heading .badge{color:#dff0d8;background-color:#3c763d}.panel-success>.panel-footer+.panel-collapse>.panel-body{border-bottom-color:#d6e9c6}.panel-info{border-color:#bce8f1}.panel-info>.panel-heading{color:#31708f;background-color:#d9edf7;border-color:#bce8f1}.panel-info>.panel-heading+.panel-collapse>.panel-body{border-top-color:#bce8f1}.panel-info>.panel-heading .badge{color:#d9edf7;background-color:#31708f}.panel-info>.panel-footer+.panel-collapse>.panel-body{border-bottom-color:#bce8f1}.panel-warning{border-color:#faebcc}.panel-warning>.panel-heading{color:#8a6d3b;background-color:#fcf8e3;border-color:#faebcc}.panel-warning>.panel-heading+.panel-collapse>.panel-body{border-top-color:#faebcc}.panel-warning>.panel-heading .badge{color:#fcf8e3;background-color:#8a6d3b}.panel-warning>.panel-footer+.panel-collapse>.panel-body{border-bottom-color:#faebcc}.panel-danger{border-color:#ebccd1}.panel-danger>.panel-heading{color:#a94442;background-color:#f2dede;border-color:#ebccd1}.panel-danger>.panel-heading+.panel-collapse>.panel-body{border-top-color:#ebccd1}.panel-danger>.panel-heading .badge{color:#f2dede;background-color:#a94442}.panel-danger>.panel-footer+.panel-collapse>.panel-body{border-bottom-color:#ebccd1}.embed-responsive{position:relative;display:block;height:0;padding:0;overflow:hidden}.embed-responsive .embed-responsive-item,.embed-responsive embed,.embed-responsive iframe,.embed-responsive object,.embed-responsive video{position:absolute;top:0;bottom:0;left:0;width:100%;height:100%;border:0}.embed-responsive-16by9{padding-bottom:56.25%}.embed-responsive-4by3{padding-bottom:75%}.well{min-height:20px;padding:19px;margin-bottom:20px;background-color:#f5f5f5;border:1px solid #e3e3e3;border-radius:4px;-webkit-box-shadow:inset 0 1px 1px rgba(0,0,0,.05);box-shadow:inset 0 1px 1px rgba(0,0,0,.05)}.well blockquote{border-color:#ddd;border-color:rgba(0,0,0,.15)}.well-lg{padding:24px;border-radius:6px}.well-sm{padding:9px;border-radius:3px}.close{float:right;font-size:21px;font-weight:700;line-height:1;color:#000;text-shadow:0 1px 0 #fff;filter:alpha(opacity=20);opacity:.2}.close:focus,.close:hover{color:#000;text-decoration:none;cursor:pointer;filter:alpha(opacity=50);opacity:.5}button.close{-webkit-appearance:none;padding:0;cursor:pointer;background:0 0;border:0}.modal-open{overflow:hidden}.modal{position:fixed;top:0;right:0;bottom:0;left:0;z-index:1050;display:none;overflow:hidden;-webkit-overflow-scrolling:touch;outline:0}.modal.fade .modal-dialog{-webkit-transition:-webkit-transform .3s ease-out;-o-transition:-o-transform .3s ease-out;transition:transform .3s ease-out;-webkit-transform:translate(0,-25%);-ms-transform:translate(0,-25%);-o-transform:translate(0,-25%);transform:translate(0,-25%)}.modal.in .modal-dialog{-webkit-transform:translate(0,0);-ms-transform:translate(0,0);-o-transform:translate(0,0);transform:translate(0,0)}.modal-open .modal{overflow-x:hidden;overflow-y:auto}.modal-dialog{position:relative;width:auto;margin:10px}.modal-content{position:relative;background-color:#fff;-webkit-background-clip:padding-box;background-clip:padding-box;border:1px solid #999;border:1px solid rgba(0,0,0,.2);border-radius:6px;outline:0;-webkit-box-shadow:0 3px 9px rgba(0,0,0,.5);box-shadow:0 3px 9px rgba(0,0,0,.5)}.modal-backdrop{position:fixed;top:0;right:0;bottom:0;left:0;z-index:1040;background-color:#000}.modal-backdrop.fade{filter:alpha(opacity=0);opacity:0}.modal-backdrop.in{filter:alpha(opacity=50);opacity:.5}.modal-header{padding:15px;border-bottom:1px solid #e5e5e5}.modal-header .close{margin-top:-2px}.modal-title{margin:0;line-height:1.42857143}.modal-body{position:relative;padding:15px}.modal-footer{padding:15px;text-align:right;border-top:1px solid #e5e5e5}.modal-footer .btn+.btn{margin-bottom:0;margin-left:5px}.modal-footer .btn-group .btn+.btn{margin-left:-1px}.modal-footer .btn-block+.btn-block{margin-left:0}.modal-scrollbar-measure{position:absolute;top:-9999px;width:50px;height:50px;overflow:scroll}@media (min-width:768px){.modal-dialog{width:600px;margin:30px auto}.modal-content{-webkit-box-shadow:0 5px 15px rgba(0,0,0,.5);box-shadow:0 5px 15px rgba(0,0,0,.5)}.modal-sm{width:300px}}@media (min-width:992px){.modal-lg{width:900px}}.tooltip{position:absolute;z-index:1070;display:block;font-family:"Helvetica Neue",Helvetica,Arial,sans-serif;font-size:12px;font-style:normal;font-weight:400;line-height:1.42857143;text-align:left;text-align:start;text-decoration:none;text-shadow:none;text-transform:none;letter-spacing:normal;word-break:normal;word-spacing:normal;word-wrap:normal;white-space:normal;filter:alpha(opacity=0);opacity:0;line-break:auto}.tooltip.in{filter:alpha(opacity=90);opacity:.9}.tooltip.top{padding:5px 0;margin-top:-3px}.tooltip.right{padding:0 5px;margin-left:3px}.tooltip.bottom{padding:5px 0;margin-top:3px}.tooltip.left{padding:0 5px;margin-left:-3px}.tooltip-inner{max-width:200px;padding:3px 8px;color:#fff;text-align:center;background-color:#000;border-radius:4px}.tooltip-arrow{position:absolute;width:0;height:0;border-color:transparent;border-style:solid}.tooltip.top .tooltip-arrow{bottom:0;left:50%;margin-left:-5px;border-width:5px 5px 0;border-top-color:#000}.tooltip.top-left .tooltip-arrow{right:5px;bottom:0;margin-bottom:-5px;border-width:5px 5px 0;border-top-color:#000}.tooltip.top-right .tooltip-arrow{bottom:0;left:5px;margin-bottom:-5px;border-width:5px 5px 0;border-top-color:#000}.tooltip.right .tooltip-arrow{top:50%;left:0;margin-top:-5px;border-width:5px 5px 5px 0;border-right-color:#000}.tooltip.left .tooltip-arrow{top:50%;right:0;margin-top:-5px;border-width:5px 0 5px 5px;border-left-color:#000}.tooltip.bottom .tooltip-arrow{top:0;left:50%;margin-left:-5px;border-width:0 5px 5px;border-bottom-color:#000}.tooltip.bottom-left .tooltip-arrow{top:0;right:5px;margin-top:-5px;border-width:0 5px 5px;border-bottom-color:#000}.tooltip.bottom-right .tooltip-arrow{top:0;left:5px;margin-top:-5px;border-width:0 5px 5px;border-bottom-color:#000}.popover{position:absolute;top:0;left:0;z-index:1060;display:none;max-width:276px;padding:1px;font-family:"Helvetica Neue",Helvetica,Arial,sans-serif;font-size:14px;font-style:normal;font-weight:400;line-height:1.42857143;text-align:left;text-align:start;text-decoration:none;text-shadow:none;text-transform:none;letter-spacing:normal;word-break:normal;word-spacing:normal;word-wrap:normal;white-space:normal;background-color:#fff;-webkit-background-clip:padding-box;background-clip:padding-box;border:1px solid #ccc;border:1px solid rgba(0,0,0,.2);border-radius:6px;-webkit-box-shadow:0 5px 10px rgba(0,0,0,.2);box-shadow:0 5px 10px rgba(0,0,0,.2);line-break:auto}.popover.top{margin-top:-10px}.popover.right{margin-left:10px}.popover.bottom{margin-top:10px}.popover.left{margin-left:-10px}.popover-title{padding:8px 14px;margin:0;font-size:14px;background-color:#f7f7f7;border-bottom:1px solid #ebebeb;border-radius:5px 5px 0 0}.popover-content{padding:9px 14px}.popover>.arrow,.popover>.arrow:after{position:absolute;display:block;width:0;height:0;border-color:transparent;border-style:solid}.popover>.arrow{border-width:11px}.popover>.arrow:after{content:"";border-width:10px}.popover.top>.arrow{bottom:-11px;left:50%;margin-left:-11px;border-top-color:#999;border-top-color:rgba(0,0,0,.25);border-bottom-width:0}.popover.top>.arrow:after{bottom:1px;margin-left:-10px;content:" ";border-top-color:#fff;border-bottom-width:0}.popover.right>.arrow{top:50%;left:-11px;margin-top:-11px;border-right-color:#999;border-right-color:rgba(0,0,0,.25);border-left-width:0}.popover.right>.arrow:after{bottom:-10px;left:1px;content:" ";border-right-color:#fff;border-left-width:0}.popover.bottom>.arrow{top:-11px;left:50%;margin-left:-11px;border-top-width:0;border-bottom-color:#999;border-bottom-color:rgba(0,0,0,.25)}.popover.bottom>.arrow:after{top:1px;margin-left:-10px;content:" ";border-top-width:0;border-bottom-color:#fff}.popover.left>.arrow{top:50%;right:-11px;margin-top:-11px;border-right-width:0;border-left-color:#999;border-left-color:rgba(0,0,0,.25)}.popover.left>.arrow:after{right:1px;bottom:-10px;content:" ";border-right-width:0;border-left-color:#fff}.carousel{position:relative}.carousel-inner{position:relative;width:100%;overflow:hidden}.carousel-inner>.item{position:relative;display:none;-webkit-transition:.6s ease-in-out left;-o-transition:.6s ease-in-out left;transition:.6s ease-in-out left}.carousel-inner>.item>a>img,.carousel-inner>.item>img{line-height:1}@media all and (transform-3d),(-webkit-transform-3d){.carousel-inner>.item{-webkit-transition:-webkit-transform .6s ease-in-out;-o-transition:-o-transform .6s ease-in-out;transition:transform .6s ease-in-out;-webkit-backface-visibility:hidden;backface-visibility:hidden;-webkit-perspective:1000px;perspective:1000px}.carousel-inner>.item.active.right,.carousel-inner>.item.next{left:0;-webkit-transform:translate3d(100%,0,0);transform:translate3d(100%,0,0)}.carousel-inner>.item.active.left,.carousel-inner>.item.prev{left:0;-webkit-transform:translate3d(-100%,0,0);transform:translate3d(-100%,0,0)}.carousel-inner>.item.active,.carousel-inner>.item.next.left,.carousel-inner>.item.prev.right{left:0;-webkit-transform:translate3d(0,0,0);transform:translate3d(0,0,0)}}.carousel-inner>.active,.carousel-inner>.next,.carousel-inner>.prev{display:block}.carousel-inner>.active{left:0}.carousel-inner>.next,.carousel-inner>.prev{position:absolute;top:0;width:100%}.carousel-inner>.next{left:100%}.carousel-inner>.prev{left:-100%}.carousel-inner>.next.left,.carousel-inner>.prev.right{left:0}.carousel-inner>.active.left{left:-100%}.carousel-inner>.active.right{left:100%}.carousel-control{position:absolute;top:0;bottom:0;left:0;width:15%;font-size:20px;color:#fff;text-align:center;text-shadow:0 1px 2px rgba(0,0,0,.6);background-color:transparent;filter:alpha(opacity=50);opacity:.5}.carousel-control.left{background-image:-webkit-linear-gradient(left,rgba(0,0,0,.5) 0,rgba(0,0,0,.0001) 100%);background-image:-o-linear-gradient(left,rgba(0,0,0,.5) 0,rgba(0,0,0,.0001) 100%);background-image:-webkit-gradient(linear,left top,right top,from(rgba(0,0,0,.5)),to(rgba(0,0,0,.0001)));background-image:linear-gradient(to right,rgba(0,0,0,.5) 0,rgba(0,0,0,.0001) 100%);filter:progid:DXImageTransform.Microsoft.gradient(startColorstr='#80000000', endColorstr='#00000000', GradientType=1);background-repeat:repeat-x}.carousel-control.right{right:0;left:auto;background-image:-webkit-linear-gradient(left,rgba(0,0,0,.0001) 0,rgba(0,0,0,.5) 100%);background-image:-o-linear-gradient(left,rgba(0,0,0,.0001) 0,rgba(0,0,0,.5) 100%);background-image:-webkit-gradient(linear,left top,right top,from(rgba(0,0,0,.0001)),to(rgba(0,0,0,.5)));background-image:linear-gradient(to right,rgba(0,0,0,.0001) 0,rgba(0,0,0,.5) 100%);filter:progid:DXImageTransform.Microsoft.gradient(startColorstr='#00000000', endColorstr='#80000000', GradientType=1);background-repeat:repeat-x}.carousel-control:focus,.carousel-control:hover{color:#fff;text-decoration:none;filter:alpha(opacity=90);outline:0;opacity:.9}.carousel-control .glyphicon-chevron-left,.carousel-control .glyphicon-chevron-right,.carousel-control .icon-next,.carousel-control .icon-prev{position:absolute;top:50%;z-index:5;display:inline-block;margin-top:-10px}.carousel-control .glyphicon-chevron-left,.carousel-control .icon-prev{left:50%;margin-left:-10px}.carousel-control .glyphicon-chevron-right,.carousel-control .icon-next{right:50%;margin-right:-10px}.carousel-control .icon-next,.carousel-control .icon-prev{width:20px;height:20px;font-family:serif;line-height:1}.carousel-control .icon-prev:before{content:'\2039'}.carousel-control .icon-next:before{content:'\203a'}.carousel-indicators{position:absolute;bottom:10px;left:50%;z-index:15;width:60%;padding-left:0;margin-left:-30%;text-align:center;list-style:none}.carousel-indicators li{display:inline-block;width:10px;height:10px;margin:1px;text-indent:-999px;cursor:pointer;background-color:transparent;border:1px solid #fff;border-radius:10px}.carousel-indicators .active{width:12px;height:12px;margin:0;background-color:#fff}.carousel-caption{position:absolute;right:15%;bottom:20px;left:15%;z-index:10;padding-top:20px;padding-bottom:20px;color:#fff;text-align:center;text-shadow:0 1px 2px rgba(0,0,0,.6)}.carousel-caption .btn{text-shadow:none}@media screen and (min-width:768px){.carousel-control .glyphicon-chevron-left,.carousel-control .glyphicon-chevron-right,.carousel-control .icon-next,.carousel-control .icon-prev{width:30px;height:30px;margin-top:-10px;font-size:30px}.carousel-control .glyphicon-chevron-left,.carousel-control .icon-prev{margin-left:-10px}.carousel-control .glyphicon-chevron-right,.carousel-control .icon-next{margin-right:-10px}.carousel-caption{right:20%;left:20%;padding-bottom:30px}.carousel-indicators{bottom:20px}}.btn-group-vertical>.btn-group:after,.btn-group-vertical>.btn-group:before,.btn-toolbar:after,.btn-toolbar:before,.clearfix:after,.clearfix:before,.container-fluid:after,.container-fluid:before,.container:after,.container:before,.dl-horizontal dd:after,.dl-horizontal dd:before,.form-horizontal .form-group:after,.form-horizontal .form-group:before,.modal-footer:after,.modal-footer:before,.modal-header:after,.modal-header:before,.nav:after,.nav:before,.navbar-collapse:after,.navbar-collapse:before,.navbar-header:after,.navbar-header:before,.navbar:after,.navbar:before,.pager:after,.pager:before,.panel-body:after,.panel-body:before,.row:after,.row:before{display:table;content:" "}.btn-group-vertical>.btn-group:after,.btn-toolbar:after,.clearfix:after,.container-fluid:after,.container:after,.dl-horizontal dd:after,.form-horizontal .form-group:after,.modal-footer:after,.modal-header:after,.nav:after,.navbar-collapse:after,.navbar-header:after,.navbar:after,.pager:after,.panel-body:after,.row:after{clear:both}.center-block{display:block;margin-right:auto;margin-left:auto}.pull-right{float:right!important}.pull-left{float:left!important}.hide{display:none!important}.show{display:block!important}.invisible{visibility:hidden}.text-hide{font:0/0 a;color:transparent;text-shadow:none;background-color:transparent;border:0}.hidden{display:none!important}.affix{position:fixed}@-ms-viewport{width:device-width}.visible-lg,.visible-lg-block,.visible-lg-inline,.visible-lg-inline-block,.visible-md,.visible-md-block,.visible-md-inline,.visible-md-inline-block,.visible-print,.visible-print-block,.visible-print-inline,.visible-print-inline-block,.visible-sm,.visible-sm-block,.visible-sm-inline,.visible-sm-inline-block,.visible-xs,.visible-xs-block,.visible-xs-inline,.visible-xs-inline-block{display:none!important}@media (max-width:767px){.visible-xs{display:block!important}table.visible-xs{display:table!important}tr.visible-xs{display:table-row!important}td.visible-xs,th.visible-xs{display:table-cell!important}}@media (max-width:767px){.visible-xs-block{display:block!important}}@media (max-width:767px){.visible-xs-inline{display:inline!important}}@media (max-width:767px){.visible-xs-inline-block{display:inline-block!important}}@media (min-width:768px) and (max-width:991px){.visible-sm{display:block!important}table.visible-sm{display:table!important}tr.visible-sm{display:table-row!important}td.visible-sm,th.visible-sm{display:table-cell!important}}@media (min-width:768px) and (max-width:991px){.visible-sm-block{display:block!important}}@media (min-width:768px) and (max-width:991px){.visible-sm-inline{display:inline!important}}@media (min-width:768px) and (max-width:991px){.visible-sm-inline-block{display:inline-block!important}}@media (min-width:992px) and (max-width:1199px){.visible-md{display:block!important}table.visible-md{display:table!important}tr.visible-md{display:table-row!important}td.visible-md,th.visible-md{display:table-cell!important}}@media (min-width:992px) and (max-width:1199px){.visible-md-block{display:block!important}}@media (min-width:992px) and (max-width:1199px){.visible-md-inline{display:inline!important}}@media (min-width:992px) and (max-width:1199px){.visible-md-inline-block{display:inline-block!important}}@media (min-width:1200px){.visible-lg{display:block!important}table.visible-lg{display:table!important}tr.visible-lg{display:table-row!important}td.visible-lg,th.visible-lg{display:table-cell!important}}@media (min-width:1200px){.visible-lg-block{display:block!important}}@media (min-width:1200px){.visible-lg-inline{display:inline!important}}@media (min-width:1200px){.visible-lg-inline-block{display:inline-block!important}}@media (max-width:767px){.hidden-xs{display:none!important}}@media (min-width:768px) and (max-width:991px){.hidden-sm{display:none!important}}@media (min-width:992px) and (max-width:1199px){.hidden-md{display:none!important}}@media (min-width:1200px){.hidden-lg{display:none!important}}@media print{.visible-print{display:block!important}table.visible-print{display:table!important}tr.visible-print{display:table-row!important}td.visible-print,th.visible-print{display:table-cell!important}}@media print{.visible-print-block{display:block!important}}@media print{.visible-print-inline{display:inline!important}}@media print{.visible-print-inline-block{display:inline-block!important}}@media print{.hidden-print{display:none!important}}.tm-tag{color:#555;background-color:#f5f5f5;border:1px solid #bbb;box-shadow:0 1px 1px rgba(0,0,0,.075) inset;display:inline-block;border-radius:3px;font-family:"Helvetica Neue",Helvetica,Arial,sans-serif;font-size:13px;margin:0 5px 5px 0;padding:4px;text-decoration:none;transition:border .2s linear 0s,box-shadow .2s linear 0s;-moz-transition:border .2s linear 0s,box-shadow .2s linear 0s;-webkit-transition:border .2s linear 0s,box-shadow .2s linear 0s;vertical-align:middle}.tm-tag .tm-tag-remove{color:#000;font-weight:700;margin-left:4px;opacity:.2}.tm-tag .tm-tag-remove:hover{color:#000;text-decoration:none;opacity:.4}.tm-tag.tm-tag-warning{color:#945203;background-color:#f2c889;border-color:#f0a12f}.tm-tag.tm-tag-error{color:#84212e;background-color:#e69ca6;border-color:#d24a5d}.tm-tag.tm-tag-success{color:#638421;background-color:#cde69c;border-color:#a5d24a}.tm-tag.tm-tag-info{color:#4594b5;background-color:#c5eefa;border-color:#5dc8f7}.tm-tag.tm-tag-inverse{color:#ccc;background-color:#555;border-color:#333;box-shadow:0 1px 1px rgba(0,0,0,.2) inset}.tm-tag.tm-tag-inverse .tm-tag-remove{color:#fff}.tm-tag.tm-tag-large{font-size:16.25px;border-radius:4px;padding:11px 7px}.tm-tag.tm-tag-small{font-size:11.05px;border-radius:3px;padding:2px 4px}.tm-tag.tm-tag-mini{font-size:9.75px;border-radius:2px;padding:0 2px}.tm-tag.tm-tag-plain{color:#333;box-shadow:none;background:0 0;border:none}.tm-tag.tm-tag-disabled{color:#aaa;background-color:#e6e6e6;border-color:#ccc;box-shadow:none}.tm-tag.tm-tag-disabled .tm-tag-remove{display:none}input[type=text].tm-input{margin-bottom:5px;vertical-align:middle!important}.control-group.tm-group{margin-bottom:5px}.form-horizontal .control-group.tm-group{margin-bottom:15px}.c3 svg{font:10px sans-serif;-webkit-tap-highlight-color:transparent}.c3 line,.c3 path{fill:none;stroke:#000}.c3 text{-webkit-user-select:none;-moz-user-select:none;user-select:none}.c3-bars path,.c3-event-rect,.c3-legend-item-tile,.c3-xgrid-focus,.c3-ygrid{shape-rendering:crispEdges}.c3-chart-arc path{stroke:#fff}.c3-chart-arc text{fill:#fff;font-size:13px}.c3-grid line{stroke:#aaa}.c3-grid text{fill:#aaa}.c3-xgrid,.c3-ygrid{stroke-dasharray:3 3}.c3-text.c3-empty{fill:gray;font-size:2em}.c3-line{stroke-width:1px}.c3-circle._expanded_{stroke-width:1px;stroke:#fff}.c3-selected-circle{fill:#fff;stroke-width:2px}.c3-bar{stroke-width:0}.c3-bar._expanded_{fill-opacity:.75}.c3-target.c3-focused{opacity:1}.c3-target.c3-focused path.c3-line,.c3-target.c3-focused path.c3-step{stroke-width:2px}.c3-target.c3-defocused{opacity:.3!important}.c3-region{fill:#4682b4;fill-opacity:.1}.c3-brush .extent{fill-opacity:.1}.c3-legend-item{font-size:12px}.c3-legend-item-hidden{opacity:.15}.c3-legend-background{opacity:.75;fill:#fff;stroke:#d3d3d3;stroke-width:1}.c3-title{font:14px sans-serif}.c3-tooltip-container{z-index:10}.c3-tooltip{border-collapse:collapse;border-spacing:0;background-color:#fff;empty-cells:show;-webkit-box-shadow:7px 7px 12px -9px #777;-moz-box-shadow:7px 7px 12px -9px #777;box-shadow:7px 7px 12px -9px #777;opacity:.9}.c3-tooltip tr{border:1px solid #CCC}.c3-tooltip th{background-color:#aaa;font-size:14px;padding:2px 5px;text-align:left;color:#FFF}.c3-tooltip td{font-size:13px;padding:3px 6px;background-color:#fff;border-left:1px dotted #999}.c3-tooltip td>span{display:inline-block;width:10px;height:10px;margin-right:6px}.c3-tooltip td.value{text-align:right}.c3-area{stroke-width:0;opacity:.2}.c3-chart-arcs-title{dominant-baseline:middle;font-size:1.3em}.c3-chart-arcs .c3-chart-arcs-background{fill:#e0e0e0;stroke:none}.c3-chart-arcs .c3-chart-arcs-gauge-unit{fill:#000;font-size:16px}.c3-chart-arcs .c3-chart-arcs-gauge-max,.c3-chart-arcs .c3-chart-arcs-gauge-min{fill:#777}.c3-chart-arc .c3-gauge-value{fill:#000}span.twitter-typeahead .tt-dropdown-menu{position:absolute;top:100%;left:0;z-index:1000;display:none;float:left;min-width:250px;padding:5px 0;margin:2px 0 0;list-style:none;font-size:14px;text-align:left;background-color:#fff;border:1px solid #ccc;border:1px solid rgba(0,0,0,.15);border-radius:4px;-webkit-box-shadow:0 6px 12px rgba(0,0,0,.175);box-shadow:0 6px 12px rgba(0,0,0,.175);background-clip:padding-box}span.twitter-typeahead .tt-suggestion>p{display:block;padding:3px 20px;clear:both;font-weight:400;line-height:1.42857143;color:#333;white-space:nowrap}span.twitter-typeahead .tt-suggestion>p:focus,span.twitter-typeahead .tt-suggestion>p:hover{text-decoration:none;outline:0;background-color:#e8e8e8}span.twitter-typeahead .tt-suggestion.tt-cursor{background-color:#f8f8f8}span.twitter-typeahead{width:100%}.input-group span.twitter-typeahead{display:block!important}.input-group span.twitter-typeahead .tt-dropdown-menu{top:32px!important}.input-group.input-group-lg span.twitter-typeahead .tt-dropdown-menu{top:44px!important}.input-group.input-group-sm span.twitter-typeahead .tt-dropdown-menu{top:28px!important}.tt-suggestion{max-width:30em;overflow:hidden}.tt-suggestion .tt-label{padding-left:1.5em}.tt-file-header,.tt-suggestion .tt-match.file{background-size:1em;background-repeat:no-repeat;background-position:5px 5px}.tt-match.predicate.built_in .tt-label{color:#00f}.tt-suggestion .tt-title{color:#555;white-space:nowrap;overflow:hidden;font-style:italic;font-size:80%}.tt-suggestion .tt-tags{max-width:100px;float:right;margin-right:2px}.tt-suggestion .tt-tag{max-width:30px;border:1px solid #ddd;padding:0 4px;margin-left:2px;border-radius:5px;background-color:#e1edff}.tt-suggestion .tt-line{white-space:nowrap}.tt-suggestion .tt-lineno{display:inline-block;width:40px;min-width:20px;font-family:monospace;color:#999;background-color:#eee;border-right:1px solid #ddd;padding:0 3px 0 5px;text-align:right}.tt-suggestion .tt-text{padding-left:5px;white-space:nowrap}div.tt-file-header{padding-left:5em;background-color:#ddd;color:#000}span.tt-path-file{font-weight:700}div.tt-match.source{overflow:hidden}table.diff{width:100%;border-collapse:collapse;border:1px solid #a9a9a9;white-space:pre-wrap}table.diff tbody{font-family:Courier,monospace}table.diff tbody th{font-family:verdana,arial,'Bitstream Vera Sans',helvetica,sans-serif;background:#EED;font-size:11px;font-weight:400;border:1px solid #BBC;color:#886;padding:.3em .5em .1em 2em;text-align:right;vertical-align:top}table.diff thead{border-bottom:1px solid #BBC;background:#EFEFEF;font-family:Verdana}table.diff thead th.texttitle{text-align:left}table.diff tbody td{padding:0;vertical-align:top}table.diff .empty{background-color:#DDD}table.diff .replace{background-color:#FD8}table.diff .delete{background-color:#E99}table.diff .skip{background-color:#EFEFEF;border:1px solid #AAA;border-right:1px solid #BBC}table.diff .insert{background-color:#9E9}table.diff th.author{text-align:right;border-top:1px solid #BBC;background:#EFEFEF}.notebook{position:relative;width:100%;height:100%}.nb-content,.nb-toolbar{width:100%}.notebook.hamburger .nb-toolbar{display:none}.nb-toolbar{position:absolute;padding-top:5px;padding-bottom:5px;margin-bottom:1em;border-bottom:1px solid #ddd}.nb-toolbar .action-fullscreen{right:5px;position:absolute}div.notebook-menu{display:none}.notebook.hamburger div.notebook-menu{display:block;position:absolute;top:3px;right:1em;z-index:2000}.notebook.hamburger .nb-view{top:0;height:100%}.nb-view{position:absolute;top:40px;height:calc(100% - 40px);width:100%;overflow-y:auto}.nb-content{position:relative;width:100%}.nb-bottom{width:100%;height:30%}.dropdown.cell-type{display:inline}.nb-cell.html:not(.runnable),.nb-cell.markdown:not(.runnable){background-color:transparent;border:0}.nb-cell{margin-left:20px;margin-right:10px;box-sizing:border-box}.nb-cell:focus{outline:0}.nb-type-select{padding:1em 0}.nb-type-select>label{margin-left:1em;margin-right:1em;position:relative;top:.1em}.nb-type-more{padding-bottom:1em;padding-left:1em}.nb-type-more label{margin-right:1em;position:relative;top:.1em}.nb-type-more input{display:inline}.nb-cell .close-select{font-size:150%;padding:0 5px;border:0;color:#888;background-color:transparent;float:right}.nb-cell.active{margin-left:8px;border-left:7px solid green!important;padding-left:5px}.nb-cell.markdown.active>div.editor{border:1px dotted #888;border-radius:5px;margin-bottom:5px;margin-right:52px}.nb-cell.singleline div.editor{height:2em}.nb-cell.singleline .CodeMirror-hscrollbar{height:0}.nb-cell .CodeMirror-scroll{max-height:40em}.nb-cell .CodeMirror{border-radius:5px}.nb-cell .nb-cell-buttons{display:inline-block;float:right}.nb-cell span.glyphicon-cloud{color:#000}.nb-cell.background span.glyphicon-cloud{color:#fff}.nb-cell>.with-buttons{background-color:#eee;border:1px solid #ccc;border-radius:5px;width:calc(100% - 50px)}.nb-cell .nb-query-menu{display:inline;float:left}.nb-query-menu button{background:0 0;padding:3px 5px 0;border:0;color:#888}.nb-query-menu button:hover{color:#000}.nb-cell .prolog-prompt{float:left;padding-right:.3em;padding-top:.25em;font-weight:700;text-align:right}.nb-cell .editor.query{margin-left:44px}.nb-cell.program,.nb-cell.query{margin-bottom:1em}.nb-cell.not-for-query,.nb-placeholder{opacity:.5}.nb-cell.markdown pre.code{width:90%;margin:auto auto 1em}.nb-cell.markdown dl.termlist{margin-left:5%}.nb-cell.markdown dl.termlist dd{margin-left:2em}.nb-cell.markdown .predicates dd{margin-left:2em;margin-bottom:1ex}a.btn-image{padding:1px 2px}.nb-cell.program span.image-icon{display:inline-block;width:18px;height:16px;padding:0;background-repeat:no-repeat;background-size:100% 100%;vertical-align:middle;background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAKAAAACgCAMAAAC8EZcfAAAAIGNIUk0AAHomAACAhAAA+gAAAIDoAAB1MAAA6mAAADqYAAAXcJy6UTwAAAAzUExURf39/dXS0qShoevY2vf09P38/Me0tGNfXzEvLwUBAS0FA14LBJ8TANAdAfklAYp4d////6nIvA0AAAAGdFJOUwD//4heJmPUefMAAAABYktHRBCVsg0sAAAACXBIWXMAAAsTAAALEwEAmpwYAAAAB3RJTUUH4AkVCzYIO9WCWAAABddJREFUeNrtXdmS3CAMBHxw2///t0Gy59yxwUYcD1FtqpKqTW1Pi24kkL2M/Y//kRSc8zmECH/CX3vDJoSQUqo9pByEmDtByWfAppT+igBz6AAkF8P4wmbClzHvKANI3pK8QW7oAixrrXuFtQ+gSopGNAJ5GzqA5r1fXhH+5QPKHaRqQSPng9rQBXDL7wCQG0Y1zHUh6vkJ7wjdE6O1O8Sa9A0SiLHWn8PbQe4Q6+V5y65xLgXeRiMmWgpdA57C9BqbiO7BIkBUK68hXqDPukv4QjhbJ818p+8qvkAi5lny0vhw9V2H9yRRFlUzB/Vat9wMj2meS+KD5eeX5T5CUxLhhs8tOVESIR9MHn9PDssoBfWbiw84LKVl8D/jloUEoaDHNwM+T4Bv07IoIRAS/sAPQSi8QIKdX+gQDhM5PkuFr8AypEwwLkPqJINCCPGFJAcKB9oSgTDBe5IJKRQXCPT4Ff82sOvaBGKrid1xQrlISWFYgQkK8c8+OPTx8YobdEK0CieRQKDHavQVJlr10FEIHhMj5AveBtFHV6GgkkhsE3ZG68sIgcKJiMDIj/qJL1p8gxdS5HgeYx5zhC+CkEomIqZhb/Vh2LP/aGisUKSk6ihOP5oj0XFUw96cADylkEbH0SVo9Wm4848mii/BcwLPKbQUizAAPF2C7hyfNhEnLL7PRTJ8mmMKlWAls5QDmG3V0X3EZACkkDGP1Ko+h0EKGfMxso9EAdpz+nMBRtulHAYXgt04uhO3BjjnAjS+OMDzFLvYTuIbM+jv78U0Ko62xO5+hoHBNZdBGQN4TqEt3TcltHTu7gpEgDPFXhzr6e4V1ERt0xoHeJxkF/1k+TV/Qld8hDB6ZUZSsCYdzGy3rdfyu7kMAUCZcvTm/559xG9EaXqS1LM39wHRpFwo07SdTJjE+5FtEAVHaNKmBShakuTTwdcRpveJt91URx9Y9C8FwlGdvwmqO7CjE0ytS9cLt+9KVgoCS1xCbBk2VPMLKZvJLQKpbsOKyCRIxHCqSSShSG/qdgKNZIqKwoGcwrACjRjp7sI0MYWE1zhPpyEVMqzAeSREKGi9cFuBlHfuCZclF2cCaAkknlnwhvAu9n0owJPtwkZxaoQ4VkG3Aukne8ALyQZ7jBQTPUIqq4HZ6gKjUejWFDqBHlUVmQfmI0mSA4FGKFaEQgqdYJ06lgFIMX/k0WJGVibmfJ2AQlZWLLJnzHAPmadiAMEMlctJcPDooqPemUmGImFlRWNQtwfRdwvkqijALCUHBZviz71kJDkoWM1jaYB6uEuhDw6jajxQcrcyxEaOVYibZogWXeWxpknoGx0UWKCq9GQYdlCu1wTfLGvAomXF59auKhktuuKjf5eV7Ir0SZHy314sYqo+3Xltx6up4Fs9XoUiJussBBvhglVqtk5Cgu3MqkdyWYMJnuoDZKlm2EAhr0Y+gcLqFviKNeXYFapA2ehVBkk6wdNo1ijmuNXA5JTUrQCq+JkhnHQ0I3C3mhiBK2sYkRueoJCmBEavJ+AssCmBEQqhTJWNX+hy6tYNPfrNrc2hW+OFV3OAJ4UhXnix5nHYJeMmp9oDPBRyIFAJxrqlEFbg0AO+IwoDgbaT12/99EL0QNUHQP5rR4ZNZGasHwr9n0LfyG5esPaDwk488K3s+qLQGi07ekMdV+bTacCk0wmsUHFL8+k0LvW8XNdpmDUMurqrJl2vVdGYY3vBY+q3Uev7rPBpoap1Ix2bV479UaWvGwr5XSY/T2N0Y6d5l8n3QwStsW1WaJ9F10cr0gW4R47NE+AmkX7AoUweOfalJouy69Z9u+ui2TzKsd8l0kud8LHI9nlwcOmhRwIfVSHFs2iF2BT4yL1VelxZnxQG7nzIsBK6T4B4IgxHlpx1GngTr6uMdqTGZz0MR9admYz+k2NNPyJ9E9v022j6MJkjlQ740t9uNbIddHXVD//M8cA6Byg6BghO2PMSRJX0DTCUXHLqGSDr7rcuVIh/P/O/AARSDtsAAAAASUVORK5CYII=)}.nb-cell.program.background span.image-icon{background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAADAAAAAwCAYAAABXAvmHAAAABmJLR0QA/wD/AP+gvaeTAAAACXBIWXMAAAsTAAALEwEAmpwYAAAAB3RJTUUH4AkUDTkUFH3ZDwAABydJREFUaN7tmWuMVdUVx38zMjgMMIioW54iUsaKSI3FJ5vWx0SMlmhVGhuIMdE2VasmRrObRkinsd1RU2kbDdSmEfGF+KhK0mBBhQ02PqZVqYIoIDMoblAcxlauysztB/+nObm95z5mbtsPzkpu9j1nr7PPWnuv9V+PAwM0QF9tqqvFIsaHEcAxwOnALOAEYAIwRCw5oBPYCKwF1gPvRmf3/l8VMD6MBO4GzgOGAQdV+Ggv0A08B1wRnd33P1XA+DAa+ClwjW71ABuADmCe7r0InAL8E3gW+A5wAHhQpzMLqBfv7wAfnd1erSz1fRD+MuD9lPC/BQ4Bzges7m2QgAD10dk5wGpgEHAJMBs4GPiVeH4AvGV8mPtfVcD48AftIMA9wPjo7HXR2X8AjwFHAe3R2ZkS8N8UnW0FVgFNwOro7IHo7I3AaGAx0AAsNz7cX3MTMj4cLDM4XfZ7YXT26dT8z4AFwKfA8Ohsr/FhGPAJsD862yS+ZmCzhL45Ont7ao0ZwBpguJx9enQ2X6sTWCPh9wBfKxD+UMABXwA2OtubtUh0thv4li5vk9DJ3MvAccAWYBqwriYmZHy4BzhDuzsuOrutgOUZYDDwQHT2r+XWi86+DdysS18w/R4wA9gHzDQ+PNIvBYwPFwFX6vIg4JcF8+cDJwG7orNXVGG6v1FsOMv4cFZKuTxwA9CoW5caH+b1yQeMD4cDu3W5AviulNipHXxajtsKXB6dXVbw/H/4QJHNeVyINlXrLALGiGU1cI4UHRmdzVV7AjdpXBadnQtMBN4AxgEPSLlW2f5D1cJfdPYJOesYYBewXP+3Cd1agUd1GiurOgHjQyOwX5eTo7NbU3MXAD8Slicb8I6w/1X93wl8BrypHRwPjNVvMjBdftWSCoRrgMVSLHnXYAFHI3BssUCXpcDdEvL+6Oz8DFjdK6zP6QX1VUT2vOA4BwwFuqOzIzJkWaJAtzA621bWhIwPTUASEa/PEOB4IU97dHaYri8CbpEpvAjsSAm7HXhJvrRAvCfo2feAZuPDNzLetUjjT4pNDipy72igGWgHPs5YdKqe3SB73qwA9WRqI+plGrno7KQSp7EEaFMO9WoRX9lkfOgAJhgfZkZn15dz4ukK6y+XiIRnaCyF+00VmtNyja0leH6tcW4lKDRT4wslFkyOe3MNyolOIdlI+VYxekrjyZUoME3jxhIvnaxxRw0U6AU+FBBknVqXULG5LAoZH95VVjktwwe69UN5fVbuMxR4S0gzNlWdFVKDEsVRypP2FOFpVhXXHZ09upwTN1dwAgl1VMDTCHxU4Wn8rcz84EpQKG2b+Ywjn5gyoboSedY4rdFRgq8OOFKy7FLVVmyt0UK1sgp8DIwEpkZnP8kILnlB3MQSudQgOWeuFJ94N0nAqdHZrozA2ancqqwTJ47ZUuKdXVp4VBnTqbRYapayWbnZcPHsr0SB11PxIIu2pZy4v1QPHCZn/zSD53ClLV2VKPB8QbAqRknEPLYGCoyRc3ZnpczApRrXV6LAJmWSM4wPWY6XBLkTM8xiKGASJzU+jFB9UIwuTpWtWZR0QB6qxIm3C+ePB44AYhGejUKE0yTweOUycxSl05lpo7A9b3zo0bMrgaXR2Q5lvWTVFMaHUyXHh9HZ18qeQHT2c7VMAJZl7Mjf5XSnGB86BZO/AE6VwL2pgNQLfCCFhygdaAN2GB/eTyA5OvuXMrvfVm1J2SMFT0qKdUHjBcDSVMDLS9gVKjHXRWd7hC65grZKnZpfFwPfBw5NbeJnwGXAk0lnQ6l9F/A58PXobGc1gewW4Fbt7Gx15Bam4LVdBX0OGBudPVAkRSg83bzaJeuA64X/LargxqtG3mp8aIvO3ie/aFDHo7PamvguBY5zjQ9r1ZFrEYS2Rme/KUEaVaBU26K0QrG90dkJQr03gUnAUuPDDpnkvlIdj/oSRfe+VGo9S/nMbGBKdHZ1qi9aB9xZpfANwB91OV/ve0Ft+VaVq0mMmdfnvlB09nXg56nCe0t0tic1/6iK+LHGB1+FDlfJ/l+Kzv4ptV4PsDWVgy2Ozq7sV2cuOrsAuFdQ9prxoaVIdZYHbjA+TKpg90fJPEl16JK5KWotjgIeAa6uRWuxTja4VDnJZuPDNSkFdwN3KNQ/o1ZIqbznlaRYj86uTc1dpQqvAVgenf1eJc3duipt9ybgNl1uAb4NfBCdzRsf3lBzdj1wppy7sDv9mDp87cDJ6mI38+Vnp6RMvSs6e21N2+sFSpwJ/F5o0asW4xLgz/KHoxQT5gnbc9HZIcaHZbq3G5iigPbDVCqxB5gfnV1V8+8DGYoskjM2pSLuKr78XpbkNmcrEK0QL7LtOal0uxu4Lzr7477I0d+PfIcJ9haWqR+K0dsKkquis7v6KkNNPrNKmSOVCpyt6qopFY2/UDESdTIPR2d3MkADNED9pn8BvSyBlToydnoAAAAASUVORK5CYII=)}.type-icon.pl{background-image:url(../icons/pl.png)}.type-icon.swinb{background-image:url(../icons/swinb.png)}.type-icon.select{background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAEAAAABACAMAAACdt4HsAAAAIGNIUk0AAHomAACAhAAA+gAAAIDoAAB1MAAA6mAAADqYAAAXcJy6UTwAAAEUUExURTAwMDQ0NDQ0NHFxcX9/f7Gxsc/Pz+np6ebm5vf39/b29tra2pCQkN3d3NLS0p6entnZ2cDAwEJCQuvr6+Xl5dnZ2fT09F9fX93d3ZqamtjY2K2trbe3t8fHx8nOw/Dv7rjDqKS8iJ63gZO4Zoe4Sn23OIq4U6y9lr7GsqnBiXi7Jn7CKpLKSp7QY53FaabUbZfLVs7SyKrLeYvHQoK/OMTKuazZc6PaWZzUVojLM4PHLbO/pI3SNqC+erHedrnWh7bGmeHi29TXycHLprDda8TZmqHJZ7zVlM7WttHZubLJieDf25baPLXjeZjXRq3iaJ3iQZvgP6XqR7Hja6zyTafjV8rYqbD2T7P5UrTvX67Clf///2wKwGIAAAAedFJOUwIXJ0JJaqba///pylP+nGHghjHqt6zfOula2HJ5ovRUycgAAAABYktHRFt0vJU0AAAACXBIWXMAAA3XAAAN1wFCKJt4AAAAB3RJTUUH4AkVDAIvILrSQQAABcRJREFUWMPNVwtb2koQJRuoy7ZBkRa5bS9JQQUJyEsegRQfKFUJNMRQrP//h9yZ3U0M9dl+97vfHSBiyDlzZmZ3djcW+3+bEl7+lEBBuKIof4QlMULgShRO81skChriAU2IqvAvyKC8Lm4OJwIej8P/RDK8ToVAK2rizcYGTYKx/Ns3iYDhJQoS4/D4uw0NsUkdX2gbKVXIgMieZ0D8JvcsTTIkk1vpbQzqeTjau40Qq7NMhuk6RQYgfR9/iQAZArhmfCkUd/d294uFUlmTKlLo4akgRPQCT42D3QraHr9W9gtlquPrg/p0IpEgIbyXiyZgq7XaYb1+2Kju7lXMSmELCCjN82Q+Vb13HN4sALpRP6y36oHV2qa5V8hSyIa2EydPlT+hc/f7FbNxj5U0tSPTLHZAg56LPyoB/McZ4o29SkNCu/yD13qv37AGlX0Dw3irkkcSocj8DSsBHoBdQdGwjo4G5lFlMDgaYhQfyEMGKHBK+DdrQjS4bnXBGvZAmIkXqwOJ1CEI5eEAwATk22ZD6u5y61scbA0CK+YoTWrb6xIUnPkoQCsGeGH1xuHXqoUmSPBPgYGGze31GMC/igGUzHY9AI+6xycdjZ2ejUu2JQ0oLMsAAooS1lOIArL7Zk3Cu+fdizMqjHUmtmUP8I0ERQ1u/bWWBRSQhalTMqvSeXc0+pbhI48zXFZtaZaUUFhPIx/DOmuYUv9oNOpe4aChjHGKcYBHiq9w71SNxqAQNQUCymY79D+6xjmcua5NxkgwnTh2KMLOM8rSkTrgJM/rGEFfEIxGs3kZOgBtAczpoJCW7dhOQDIEXYW1QipxEECLplAP9t2+BsbO3AE7QQnX+C3g+AJp+ahEkgDTAAjO2uaxwM9Gjt0v02yLo8b3BJzEtotTRpORQkIREuAvb7Wl/1kPXLk17t+ZX8Fv08nCWYQcjQxlyZ2QAFeQtI45nHOCGQrgDy4ANR9jNcaAdgMJTrUJt3bWFKQhBMPsA/wYCHoc7wKB646xGV72XA++BxqqW1DISBmglXyCHBpWn/ufzeRzruN6mEv97NxFW7gLMPxl65RBHUlkGHyGxwxrLvA3HM0twHuu63mCBSjmHcYym2FfwmaWTlK9Y7UhfCDo8fDhYa83hTmeOffQXHwJgn6W0akatnck2IEQ8m17NhMRoFR0d4GLy8gLTUqYaIwxNRICxAAKMg27yyNwBRwA32CKXiLS9wIVSNGaMtaMNFZs6Dhwv9g9mQJB4HrLS3p17vu+xz9CA7xhKLNCZHlAghSsOoY9R4KlI+Ho+WbpCwOOMIwOnbLNaGvHJQmGa7Pq3CCBKICLwo9/XPj3xkW43iQz5SmIxqCoWYjBaPdns+NlgPd8yIF+sVrdgq38QII3pIxurPU0rEMhSWmHS3AXEu/5l5DEH/cEgmOSg9mcWutISBAHAnbtzGfHtwuZAV8Q3HJbrVYyBkyhrpK1roo7lwJMkGbD+TnzAwGeB+MgeXEbMAgBrSwQpH5ZWbgErORw7nxfLgIC/+bq9OpnlMD3egZjyQz5tatjJd9gC71znCUPAYuAdhsaJ1gaUIHk54drIy7OOZik2oETDEMPa7+6XUVy4HslHMW57Yd4bAqb2MLPDuZumASAAPC+jMvSFPE75NEdI7QVoKdaaR4m0ZcMwr1/jgVgGfWJjRbc/hs0MGZMnEgQnIRfu2XEs7RKntjjqMiAYTTv+nIuhBS+XzeaGihsph/fY/FNNpFRnLL8Xd8L48Dh0z1poncqGhF5Zp8ahw0ErFwsY9zVJ0skWJ4fnJQzXD0bqs/gg3U6RdEVZqvZKRvlcqeJaFCmaWkcss/iuYp4SscxtW56UvvM95gkFnt5v72Zyv1KkEupr0CHIiCb6Y8Ag20Tyh+mdwh5Ifo1EZxEVbYTiU/pdFwoF/DXMUgRJECK0xv5vWMficljX4wQ5c9OjjF5zBLnxn/hCPwfI19t/wAe25dChuNuFgAAAABJRU5ErkJggg==)}div.feedback{position:absolute;bottom:3px;left:0;right:3px;padding:0 10px 3px;z-index:1000;border:1px solid #888;border-radius:5px;background-color:#cff;box-shadow:3px 3px 5px #888}div.feedback.warning{background-color:#fdd}.modal-header .glyphicon-warning-sign{color:#fa0;font-size:150%}.modal-header .warning{color:red}div.btn-group.diff{margin-top:1em}div.btn-transparent button.dropdown-toggle{background:none;border:0;cursor:pointer;padding:0;color:#000;float:right;font-size:16px;font-weight:700;line-height:1;opacity:.2}div.btn-transparent>button:hover{opacity:.8}a.pengine-logo{position:absolute;top:4px;left:4px;width:42px;height:42px;background-image:url(../icons/logo.png);background-size:100%}.splitter_panel .hsplitter,.splitter_panel .vsplitter{z-index:100;border:2px outset #ccc}.splitter_panel .vsplitter{width:3px}.splitter_panel .hsplitter{height:3px}.splitter_panel .bottom_panel,.splitter_panel .hsplitter,.splitter_panel .left_panel,.splitter_panel .right_panel,.splitter_panel .top_panel,.splitter_panel .vsplitter{overflow:visible}body .modal-dialog{width:80%;max-width:800px;margin-left:auto;margin-right:auto}body .modal-dialog.modal-wide{width:90%;max-width:none}body .modal-dialog.swish-embedded-manual{width:90%;max-width:1000px}body .modal-dialog.swish-embedded-manual div.modal-body{padding:0}iframe.swish-embedded-manual{width:100%;border:0}
\ No newline at end of file
+ *//*! normalize.css v3.0.3 | MIT License | github.com/necolas/normalize.css */html{font-family:sans-serif;-webkit-text-size-adjust:100%;-ms-text-size-adjust:100%}body{margin:0}article,aside,details,figcaption,figure,footer,header,hgroup,main,menu,nav,section,summary{display:block}audio,canvas,progress,video{display:inline-block;vertical-align:baseline}audio:not([controls]){display:none;height:0}[hidden],template{display:none}a{background-color:transparent}a:active,a:hover{outline:0}abbr[title]{border-bottom:1px dotted}b,strong{font-weight:700}dfn{font-style:italic}h1{margin:.67em 0;font-size:2em}mark{color:#000;background:#ff0}small{font-size:80%}sub,sup{position:relative;font-size:75%;line-height:0;vertical-align:baseline}sup{top:-.5em}sub{bottom:-.25em}img{border:0}svg:not(:root){overflow:hidden}figure{margin:1em 40px}hr{height:0;-webkit-box-sizing:content-box;-moz-box-sizing:content-box;box-sizing:content-box}pre{overflow:auto}code,kbd,pre,samp{font-family:monospace,monospace;font-size:1em}button,input,optgroup,select,textarea{margin:0;font:inherit;color:inherit}button{overflow:visible}button,select{text-transform:none}button,html input[type=button],input[type=reset],input[type=submit]{-webkit-appearance:button;cursor:pointer}button[disabled],html input[disabled]{cursor:default}button::-moz-focus-inner,input::-moz-focus-inner{padding:0;border:0}input{line-height:normal}input[type=checkbox],input[type=radio]{-webkit-box-sizing:border-box;-moz-box-sizing:border-box;box-sizing:border-box;padding:0}input[type=number]::-webkit-inner-spin-button,input[type=number]::-webkit-outer-spin-button{height:auto}input[type=search]{-webkit-box-sizing:content-box;-moz-box-sizing:content-box;box-sizing:content-box;-webkit-appearance:textfield}input[type=search]::-webkit-search-cancel-button,input[type=search]::-webkit-search-decoration{-webkit-appearance:none}fieldset{padding:.35em .625em .75em;margin:0 2px;border:1px solid silver}legend{padding:0;border:0}textarea{overflow:auto}optgroup{font-weight:700}table{border-spacing:0;border-collapse:collapse}td,th{padding:0}/*! Source: https://github.com/h5bp/html5-boilerplate/blob/master/src/css/main.css */@media print{*,:after,:before{color:#000!important;text-shadow:none!important;background:0 0!important;-webkit-box-shadow:none!important;box-shadow:none!important}a,a:visited{text-decoration:underline}a[href]:after{content:" (" attr(href) ")"}abbr[title]:after{content:" (" attr(title) ")"}a[href^="#"]:after,a[href^="javascript:"]:after{content:""}blockquote,pre{border:1px solid #999;page-break-inside:avoid}thead{display:table-header-group}img,tr{page-break-inside:avoid}img{max-width:100%!important}h2,h3,p{orphans:3;widows:3}h2,h3{page-break-after:avoid}.navbar{display:none}.btn>.caret,.dropup>.btn>.caret{border-top-color:#000!important}.label{border:1px solid #000}.table{border-collapse:collapse!important}.table td,.table th{background-color:#fff!important}.table-bordered td,.table-bordered th{border:1px solid #ddd!important}}@font-face{font-family:'Glyphicons Halflings';src:url(../bower_components/bootstrap/dist/fonts/glyphicons-halflings-regular.eot);src:url(../bower_components/bootstrap/dist/fonts/glyphicons-halflings-regular.eot?#iefix) format('embedded-opentype'),url(../bower_components/bootstrap/dist/fonts/glyphicons-halflings-regular.woff2) format('woff2'),url(../bower_components/bootstrap/dist/fonts/glyphicons-halflings-regular.woff) format('woff'),url(../bower_components/bootstrap/dist/fonts/glyphicons-halflings-regular.ttf) format('truetype'),url(../bower_components/bootstrap/dist/fonts/glyphicons-halflings-regular.svg#glyphicons_halflingsregular) format('svg')}.glyphicon{position:relative;top:1px;display:inline-block;font-family:'Glyphicons Halflings';font-style:normal;font-weight:400;line-height:1;-webkit-font-smoothing:antialiased;-moz-osx-font-smoothing:grayscale}.glyphicon-asterisk:before{content:"\002a"}.glyphicon-plus:before{content:"\002b"}.glyphicon-eur:before,.glyphicon-euro:before{content:"\20ac"}.glyphicon-minus:before{content:"\2212"}.glyphicon-cloud:before{content:"\2601"}.glyphicon-envelope:before{content:"\2709"}.glyphicon-pencil:before{content:"\270f"}.glyphicon-glass:before{content:"\e001"}.glyphicon-music:before{content:"\e002"}.glyphicon-search:before{content:"\e003"}.glyphicon-heart:before{content:"\e005"}.glyphicon-star:before{content:"\e006"}.glyphicon-star-empty:before{content:"\e007"}.glyphicon-user:before{content:"\e008"}.glyphicon-film:before{content:"\e009"}.glyphicon-th-large:before{content:"\e010"}.glyphicon-th:before{content:"\e011"}.glyphicon-th-list:before{content:"\e012"}.glyphicon-ok:before{content:"\e013"}.glyphicon-remove:before{content:"\e014"}.glyphicon-zoom-in:before{content:"\e015"}.glyphicon-zoom-out:before{content:"\e016"}.glyphicon-off:before{content:"\e017"}.glyphicon-signal:before{content:"\e018"}.glyphicon-cog:before{content:"\e019"}.glyphicon-trash:before{content:"\e020"}.glyphicon-home:before{content:"\e021"}.glyphicon-file:before{content:"\e022"}.glyphicon-time:before{content:"\e023"}.glyphicon-road:before{content:"\e024"}.glyphicon-download-alt:before{content:"\e025"}.glyphicon-download:before{content:"\e026"}.glyphicon-upload:before{content:"\e027"}.glyphicon-inbox:before{content:"\e028"}.glyphicon-play-circle:before{content:"\e029"}.glyphicon-repeat:before{content:"\e030"}.glyphicon-refresh:before{content:"\e031"}.glyphicon-list-alt:before{content:"\e032"}.glyphicon-lock:before{content:"\e033"}.glyphicon-flag:before{content:"\e034"}.glyphicon-headphones:before{content:"\e035"}.glyphicon-volume-off:before{content:"\e036"}.glyphicon-volume-down:before{content:"\e037"}.glyphicon-volume-up:before{content:"\e038"}.glyphicon-qrcode:before{content:"\e039"}.glyphicon-barcode:before{content:"\e040"}.glyphicon-tag:before{content:"\e041"}.glyphicon-tags:before{content:"\e042"}.glyphicon-book:before{content:"\e043"}.glyphicon-bookmark:before{content:"\e044"}.glyphicon-print:before{content:"\e045"}.glyphicon-camera:before{content:"\e046"}.glyphicon-font:before{content:"\e047"}.glyphicon-bold:before{content:"\e048"}.glyphicon-italic:before{content:"\e049"}.glyphicon-text-height:before{content:"\e050"}.glyphicon-text-width:before{content:"\e051"}.glyphicon-align-left:before{content:"\e052"}.glyphicon-align-center:before{content:"\e053"}.glyphicon-align-right:before{content:"\e054"}.glyphicon-align-justify:before{content:"\e055"}.glyphicon-list:before{content:"\e056"}.glyphicon-indent-left:before{content:"\e057"}.glyphicon-indent-right:before{content:"\e058"}.glyphicon-facetime-video:before{content:"\e059"}.glyphicon-picture:before{content:"\e060"}.glyphicon-map-marker:before{content:"\e062"}.glyphicon-adjust:before{content:"\e063"}.glyphicon-tint:before{content:"\e064"}.glyphicon-edit:before{content:"\e065"}.glyphicon-share:before{content:"\e066"}.glyphicon-check:before{content:"\e067"}.glyphicon-move:before{content:"\e068"}.glyphicon-step-backward:before{content:"\e069"}.glyphicon-fast-backward:before{content:"\e070"}.glyphicon-backward:before{content:"\e071"}.glyphicon-play:before{content:"\e072"}.glyphicon-pause:before{content:"\e073"}.glyphicon-stop:before{content:"\e074"}.glyphicon-forward:before{content:"\e075"}.glyphicon-fast-forward:before{content:"\e076"}.glyphicon-step-forward:before{content:"\e077"}.glyphicon-eject:before{content:"\e078"}.glyphicon-chevron-left:before{content:"\e079"}.glyphicon-chevron-right:before{content:"\e080"}.glyphicon-plus-sign:before{content:"\e081"}.glyphicon-minus-sign:before{content:"\e082"}.glyphicon-remove-sign:before{content:"\e083"}.glyphicon-ok-sign:before{content:"\e084"}.glyphicon-question-sign:before{content:"\e085"}.glyphicon-info-sign:before{content:"\e086"}.glyphicon-screenshot:before{content:"\e087"}.glyphicon-remove-circle:before{content:"\e088"}.glyphicon-ok-circle:before{content:"\e089"}.glyphicon-ban-circle:before{content:"\e090"}.glyphicon-arrow-left:before{content:"\e091"}.glyphicon-arrow-right:before{content:"\e092"}.glyphicon-arrow-up:before{content:"\e093"}.glyphicon-arrow-down:before{content:"\e094"}.glyphicon-share-alt:before{content:"\e095"}.glyphicon-resize-full:before{content:"\e096"}.glyphicon-resize-small:before{content:"\e097"}.glyphicon-exclamation-sign:before{content:"\e101"}.glyphicon-gift:before{content:"\e102"}.glyphicon-leaf:before{content:"\e103"}.glyphicon-fire:before{content:"\e104"}.glyphicon-eye-open:before{content:"\e105"}.glyphicon-eye-close:before{content:"\e106"}.glyphicon-warning-sign:before{content:"\e107"}.glyphicon-plane:before{content:"\e108"}.glyphicon-calendar:before{content:"\e109"}.glyphicon-random:before{content:"\e110"}.glyphicon-comment:before{content:"\e111"}.glyphicon-magnet:before{content:"\e112"}.glyphicon-chevron-up:before{content:"\e113"}.glyphicon-chevron-down:before{content:"\e114"}.glyphicon-retweet:before{content:"\e115"}.glyphicon-shopping-cart:before{content:"\e116"}.glyphicon-folder-close:before{content:"\e117"}.glyphicon-folder-open:before{content:"\e118"}.glyphicon-resize-vertical:before{content:"\e119"}.glyphicon-resize-horizontal:before{content:"\e120"}.glyphicon-hdd:before{content:"\e121"}.glyphicon-bullhorn:before{content:"\e122"}.glyphicon-bell:before{content:"\e123"}.glyphicon-certificate:before{content:"\e124"}.glyphicon-thumbs-up:before{content:"\e125"}.glyphicon-thumbs-down:before{content:"\e126"}.glyphicon-hand-right:before{content:"\e127"}.glyphicon-hand-left:before{content:"\e128"}.glyphicon-hand-up:before{content:"\e129"}.glyphicon-hand-down:before{content:"\e130"}.glyphicon-circle-arrow-right:before{content:"\e131"}.glyphicon-circle-arrow-left:before{content:"\e132"}.glyphicon-circle-arrow-up:before{content:"\e133"}.glyphicon-circle-arrow-down:before{content:"\e134"}.glyphicon-globe:before{content:"\e135"}.glyphicon-wrench:before{content:"\e136"}.glyphicon-tasks:before{content:"\e137"}.glyphicon-filter:before{content:"\e138"}.glyphicon-briefcase:before{content:"\e139"}.glyphicon-fullscreen:before{content:"\e140"}.glyphicon-dashboard:before{content:"\e141"}.glyphicon-paperclip:before{content:"\e142"}.glyphicon-heart-empty:before{content:"\e143"}.glyphicon-link:before{content:"\e144"}.glyphicon-phone:before{content:"\e145"}.glyphicon-pushpin:before{content:"\e146"}.glyphicon-usd:before{content:"\e148"}.glyphicon-gbp:before{content:"\e149"}.glyphicon-sort:before{content:"\e150"}.glyphicon-sort-by-alphabet:before{content:"\e151"}.glyphicon-sort-by-alphabet-alt:before{content:"\e152"}.glyphicon-sort-by-order:before{content:"\e153"}.glyphicon-sort-by-order-alt:before{content:"\e154"}.glyphicon-sort-by-attributes:before{content:"\e155"}.glyphicon-sort-by-attributes-alt:before{content:"\e156"}.glyphicon-unchecked:before{content:"\e157"}.glyphicon-expand:before{content:"\e158"}.glyphicon-collapse-down:before{content:"\e159"}.glyphicon-collapse-up:before{content:"\e160"}.glyphicon-log-in:before{content:"\e161"}.glyphicon-flash:before{content:"\e162"}.glyphicon-log-out:before{content:"\e163"}.glyphicon-new-window:before{content:"\e164"}.glyphicon-record:before{content:"\e165"}.glyphicon-save:before{content:"\e166"}.glyphicon-open:before{content:"\e167"}.glyphicon-saved:before{content:"\e168"}.glyphicon-import:before{content:"\e169"}.glyphicon-export:before{content:"\e170"}.glyphicon-send:before{content:"\e171"}.glyphicon-floppy-disk:before{content:"\e172"}.glyphicon-floppy-saved:before{content:"\e173"}.glyphicon-floppy-remove:before{content:"\e174"}.glyphicon-floppy-save:before{content:"\e175"}.glyphicon-floppy-open:before{content:"\e176"}.glyphicon-credit-card:before{content:"\e177"}.glyphicon-transfer:before{content:"\e178"}.glyphicon-cutlery:before{content:"\e179"}.glyphicon-header:before{content:"\e180"}.glyphicon-compressed:before{content:"\e181"}.glyphicon-earphone:before{content:"\e182"}.glyphicon-phone-alt:before{content:"\e183"}.glyphicon-tower:before{content:"\e184"}.glyphicon-stats:before{content:"\e185"}.glyphicon-sd-video:before{content:"\e186"}.glyphicon-hd-video:before{content:"\e187"}.glyphicon-subtitles:before{content:"\e188"}.glyphicon-sound-stereo:before{content:"\e189"}.glyphicon-sound-dolby:before{content:"\e190"}.glyphicon-sound-5-1:before{content:"\e191"}.glyphicon-sound-6-1:before{content:"\e192"}.glyphicon-sound-7-1:before{content:"\e193"}.glyphicon-copyright-mark:before{content:"\e194"}.glyphicon-registration-mark:before{content:"\e195"}.glyphicon-cloud-download:before{content:"\e197"}.glyphicon-cloud-upload:before{content:"\e198"}.glyphicon-tree-conifer:before{content:"\e199"}.glyphicon-tree-deciduous:before{content:"\e200"}.glyphicon-cd:before{content:"\e201"}.glyphicon-save-file:before{content:"\e202"}.glyphicon-open-file:before{content:"\e203"}.glyphicon-level-up:before{content:"\e204"}.glyphicon-copy:before{content:"\e205"}.glyphicon-paste:before{content:"\e206"}.glyphicon-alert:before{content:"\e209"}.glyphicon-equalizer:before{content:"\e210"}.glyphicon-king:before{content:"\e211"}.glyphicon-queen:before{content:"\e212"}.glyphicon-pawn:before{content:"\e213"}.glyphicon-bishop:before{content:"\e214"}.glyphicon-knight:before{content:"\e215"}.glyphicon-baby-formula:before{content:"\e216"}.glyphicon-tent:before{content:"\26fa"}.glyphicon-blackboard:before{content:"\e218"}.glyphicon-bed:before{content:"\e219"}.glyphicon-apple:before{content:"\f8ff"}.glyphicon-erase:before{content:"\e221"}.glyphicon-hourglass:before{content:"\231b"}.glyphicon-lamp:before{content:"\e223"}.glyphicon-duplicate:before{content:"\e224"}.glyphicon-piggy-bank:before{content:"\e225"}.glyphicon-scissors:before{content:"\e226"}.glyphicon-bitcoin:before{content:"\e227"}.glyphicon-btc:before{content:"\e227"}.glyphicon-xbt:before{content:"\e227"}.glyphicon-yen:before{content:"\00a5"}.glyphicon-jpy:before{content:"\00a5"}.glyphicon-ruble:before{content:"\20bd"}.glyphicon-rub:before{content:"\20bd"}.glyphicon-scale:before{content:"\e230"}.glyphicon-ice-lolly:before{content:"\e231"}.glyphicon-ice-lolly-tasted:before{content:"\e232"}.glyphicon-education:before{content:"\e233"}.glyphicon-option-horizontal:before{content:"\e234"}.glyphicon-option-vertical:before{content:"\e235"}.glyphicon-menu-hamburger:before{content:"\e236"}.glyphicon-modal-window:before{content:"\e237"}.glyphicon-oil:before{content:"\e238"}.glyphicon-grain:before{content:"\e239"}.glyphicon-sunglasses:before{content:"\e240"}.glyphicon-text-size:before{content:"\e241"}.glyphicon-text-color:before{content:"\e242"}.glyphicon-text-background:before{content:"\e243"}.glyphicon-object-align-top:before{content:"\e244"}.glyphicon-object-align-bottom:before{content:"\e245"}.glyphicon-object-align-horizontal:before{content:"\e246"}.glyphicon-object-align-left:before{content:"\e247"}.glyphicon-object-align-vertical:before{content:"\e248"}.glyphicon-object-align-right:before{content:"\e249"}.glyphicon-triangle-right:before{content:"\e250"}.glyphicon-triangle-left:before{content:"\e251"}.glyphicon-triangle-bottom:before{content:"\e252"}.glyphicon-triangle-top:before{content:"\e253"}.glyphicon-console:before{content:"\e254"}.glyphicon-superscript:before{content:"\e255"}.glyphicon-subscript:before{content:"\e256"}.glyphicon-menu-left:before{content:"\e257"}.glyphicon-menu-right:before{content:"\e258"}.glyphicon-menu-down:before{content:"\e259"}.glyphicon-menu-up:before{content:"\e260"}*{-webkit-box-sizing:border-box;-moz-box-sizing:border-box;box-sizing:border-box}:after,:before{-webkit-box-sizing:border-box;-moz-box-sizing:border-box;box-sizing:border-box}html{font-size:10px;-webkit-tap-highlight-color:transparent}body{font-family:"Helvetica Neue",Helvetica,Arial,sans-serif;font-size:14px;line-height:1.42857143;color:#333;background-color:#fff}button,input,select,textarea{font-family:inherit;font-size:inherit;line-height:inherit}a{color:#337ab7;text-decoration:none}a:focus,a:hover{color:#23527c;text-decoration:underline}a:focus{outline:5px auto -webkit-focus-ring-color;outline-offset:-2px}figure{margin:0}img{vertical-align:middle}.carousel-inner>.item>a>img,.carousel-inner>.item>img,.img-responsive,.thumbnail a>img,.thumbnail>img{display:block;max-width:100%;height:auto}.img-rounded{border-radius:6px}.img-thumbnail{display:inline-block;max-width:100%;height:auto;padding:4px;line-height:1.42857143;background-color:#fff;border:1px solid #ddd;border-radius:4px;-webkit-transition:all .2s ease-in-out;-o-transition:all .2s ease-in-out;transition:all .2s ease-in-out}.img-circle{border-radius:50%}hr{margin-top:20px;margin-bottom:20px;border:0;border-top:1px solid #eee}.sr-only{position:absolute;width:1px;height:1px;padding:0;margin:-1px;overflow:hidden;clip:rect(0,0,0,0);border:0}.sr-only-focusable:active,.sr-only-focusable:focus{position:static;width:auto;height:auto;margin:0;overflow:visible;clip:auto}[role=button]{cursor:pointer}.h1,.h2,.h3,.h4,.h5,.h6,h1,h2,h3,h4,h5,h6{font-family:inherit;font-weight:500;line-height:1.1;color:inherit}.h1 .small,.h1 small,.h2 .small,.h2 small,.h3 .small,.h3 small,.h4 .small,.h4 small,.h5 .small,.h5 small,.h6 .small,.h6 small,h1 .small,h1 small,h2 .small,h2 small,h3 .small,h3 small,h4 .small,h4 small,h5 .small,h5 small,h6 .small,h6 small{font-weight:400;line-height:1;color:#777}.h1,.h2,.h3,h1,h2,h3{margin-top:20px;margin-bottom:10px}.h1 .small,.h1 small,.h2 .small,.h2 small,.h3 .small,.h3 small,h1 .small,h1 small,h2 .small,h2 small,h3 .small,h3 small{font-size:65%}.h4,.h5,.h6,h4,h5,h6{margin-top:10px;margin-bottom:10px}.h4 .small,.h4 small,.h5 .small,.h5 small,.h6 .small,.h6 small,h4 .small,h4 small,h5 .small,h5 small,h6 .small,h6 small{font-size:75%}.h1,h1{font-size:36px}.h2,h2{font-size:30px}.h3,h3{font-size:24px}.h4,h4{font-size:18px}.h5,h5{font-size:14px}.h6,h6{font-size:12px}p{margin:0 0 10px}.lead{margin-bottom:20px;font-size:16px;font-weight:300;line-height:1.4}@media (min-width:768px){.lead{font-size:21px}}.small,small{font-size:85%}.mark,mark{padding:.2em;background-color:#fcf8e3}.text-left{text-align:left}.text-right{text-align:right}.text-center{text-align:center}.text-justify{text-align:justify}.text-nowrap{white-space:nowrap}.text-lowercase{text-transform:lowercase}.text-uppercase{text-transform:uppercase}.text-capitalize{text-transform:capitalize}.text-muted{color:#777}.text-primary{color:#337ab7}a.text-primary:focus,a.text-primary:hover{color:#286090}.text-success{color:#3c763d}a.text-success:focus,a.text-success:hover{color:#2b542c}.text-info{color:#31708f}a.text-info:focus,a.text-info:hover{color:#245269}.text-warning{color:#8a6d3b}a.text-warning:focus,a.text-warning:hover{color:#66512c}.text-danger{color:#a94442}a.text-danger:focus,a.text-danger:hover{color:#843534}.bg-primary{color:#fff;background-color:#337ab7}a.bg-primary:focus,a.bg-primary:hover{background-color:#286090}.bg-success{background-color:#dff0d8}a.bg-success:focus,a.bg-success:hover{background-color:#c1e2b3}.bg-info{background-color:#d9edf7}a.bg-info:focus,a.bg-info:hover{background-color:#afd9ee}.bg-warning{background-color:#fcf8e3}a.bg-warning:focus,a.bg-warning:hover{background-color:#f7ecb5}.bg-danger{background-color:#f2dede}a.bg-danger:focus,a.bg-danger:hover{background-color:#e4b9b9}.page-header{padding-bottom:9px;margin:40px 0 20px;border-bottom:1px solid #eee}ol,ul{margin-top:0;margin-bottom:10px}ol ol,ol ul,ul ol,ul ul{margin-bottom:0}.list-unstyled{padding-left:0;list-style:none}.list-inline{padding-left:0;margin-left:-5px;list-style:none}.list-inline>li{display:inline-block;padding-right:5px;padding-left:5px}dl{margin-top:0;margin-bottom:20px}dd,dt{line-height:1.42857143}dt{font-weight:700}dd{margin-left:0}@media (min-width:768px){.dl-horizontal dt{float:left;width:160px;overflow:hidden;clear:left;text-align:right;text-overflow:ellipsis;white-space:nowrap}.dl-horizontal dd{margin-left:180px}}abbr[data-original-title],abbr[title]{cursor:help;border-bottom:1px dotted #777}.initialism{font-size:90%;text-transform:uppercase}blockquote{padding:10px 20px;margin:0 0 20px;font-size:17.5px;border-left:5px solid #eee}blockquote ol:last-child,blockquote p:last-child,blockquote ul:last-child{margin-bottom:0}blockquote .small,blockquote footer,blockquote small{display:block;font-size:80%;line-height:1.42857143;color:#777}blockquote .small:before,blockquote footer:before,blockquote small:before{content:'\2014 \00A0'}.blockquote-reverse,blockquote.pull-right{padding-right:15px;padding-left:0;text-align:right;border-right:5px solid #eee;border-left:0}.blockquote-reverse .small:before,.blockquote-reverse footer:before,.blockquote-reverse small:before,blockquote.pull-right .small:before,blockquote.pull-right footer:before,blockquote.pull-right small:before{content:''}.blockquote-reverse .small:after,.blockquote-reverse footer:after,.blockquote-reverse small:after,blockquote.pull-right .small:after,blockquote.pull-right footer:after,blockquote.pull-right small:after{content:'\00A0 \2014'}address{margin-bottom:20px;font-style:normal;line-height:1.42857143}code,kbd,pre,samp{font-family:Menlo,Monaco,Consolas,"Courier New",monospace}code{padding:2px 4px;font-size:90%;color:#c7254e;background-color:#f9f2f4;border-radius:4px}kbd{padding:2px 4px;font-size:90%;color:#fff;background-color:#333;border-radius:3px;-webkit-box-shadow:inset 0 -1px 0 rgba(0,0,0,.25);box-shadow:inset 0 -1px 0 rgba(0,0,0,.25)}kbd kbd{padding:0;font-size:100%;font-weight:700;-webkit-box-shadow:none;box-shadow:none}pre{display:block;padding:9.5px;margin:0 0 10px;font-size:13px;line-height:1.42857143;color:#333;word-break:break-all;word-wrap:break-word;background-color:#f5f5f5;border:1px solid #ccc;border-radius:4px}pre code{padding:0;font-size:inherit;color:inherit;white-space:pre-wrap;background-color:transparent;border-radius:0}.pre-scrollable{max-height:340px;overflow-y:scroll}.container{padding-right:15px;padding-left:15px;margin-right:auto;margin-left:auto}@media (min-width:768px){.container{width:750px}}@media (min-width:992px){.container{width:970px}}@media (min-width:1200px){.container{width:1170px}}.container-fluid{padding-right:15px;padding-left:15px;margin-right:auto;margin-left:auto}.row{margin-right:-15px;margin-left:-15px}.col-lg-1,.col-lg-10,.col-lg-11,.col-lg-12,.col-lg-2,.col-lg-3,.col-lg-4,.col-lg-5,.col-lg-6,.col-lg-7,.col-lg-8,.col-lg-9,.col-md-1,.col-md-10,.col-md-11,.col-md-12,.col-md-2,.col-md-3,.col-md-4,.col-md-5,.col-md-6,.col-md-7,.col-md-8,.col-md-9,.col-sm-1,.col-sm-10,.col-sm-11,.col-sm-12,.col-sm-2,.col-sm-3,.col-sm-4,.col-sm-5,.col-sm-6,.col-sm-7,.col-sm-8,.col-sm-9,.col-xs-1,.col-xs-10,.col-xs-11,.col-xs-12,.col-xs-2,.col-xs-3,.col-xs-4,.col-xs-5,.col-xs-6,.col-xs-7,.col-xs-8,.col-xs-9{position:relative;min-height:1px;padding-right:15px;padding-left:15px}.col-xs-1,.col-xs-10,.col-xs-11,.col-xs-12,.col-xs-2,.col-xs-3,.col-xs-4,.col-xs-5,.col-xs-6,.col-xs-7,.col-xs-8,.col-xs-9{float:left}.col-xs-12{width:100%}.col-xs-11{width:91.66666667%}.col-xs-10{width:83.33333333%}.col-xs-9{width:75%}.col-xs-8{width:66.66666667%}.col-xs-7{width:58.33333333%}.col-xs-6{width:50%}.col-xs-5{width:41.66666667%}.col-xs-4{width:33.33333333%}.col-xs-3{width:25%}.col-xs-2{width:16.66666667%}.col-xs-1{width:8.33333333%}.col-xs-pull-12{right:100%}.col-xs-pull-11{right:91.66666667%}.col-xs-pull-10{right:83.33333333%}.col-xs-pull-9{right:75%}.col-xs-pull-8{right:66.66666667%}.col-xs-pull-7{right:58.33333333%}.col-xs-pull-6{right:50%}.col-xs-pull-5{right:41.66666667%}.col-xs-pull-4{right:33.33333333%}.col-xs-pull-3{right:25%}.col-xs-pull-2{right:16.66666667%}.col-xs-pull-1{right:8.33333333%}.col-xs-pull-0{right:auto}.col-xs-push-12{left:100%}.col-xs-push-11{left:91.66666667%}.col-xs-push-10{left:83.33333333%}.col-xs-push-9{left:75%}.col-xs-push-8{left:66.66666667%}.col-xs-push-7{left:58.33333333%}.col-xs-push-6{left:50%}.col-xs-push-5{left:41.66666667%}.col-xs-push-4{left:33.33333333%}.col-xs-push-3{left:25%}.col-xs-push-2{left:16.66666667%}.col-xs-push-1{left:8.33333333%}.col-xs-push-0{left:auto}.col-xs-offset-12{margin-left:100%}.col-xs-offset-11{margin-left:91.66666667%}.col-xs-offset-10{margin-left:83.33333333%}.col-xs-offset-9{margin-left:75%}.col-xs-offset-8{margin-left:66.66666667%}.col-xs-offset-7{margin-left:58.33333333%}.col-xs-offset-6{margin-left:50%}.col-xs-offset-5{margin-left:41.66666667%}.col-xs-offset-4{margin-left:33.33333333%}.col-xs-offset-3{margin-left:25%}.col-xs-offset-2{margin-left:16.66666667%}.col-xs-offset-1{margin-left:8.33333333%}.col-xs-offset-0{margin-left:0}@media (min-width:768px){.col-sm-1,.col-sm-10,.col-sm-11,.col-sm-12,.col-sm-2,.col-sm-3,.col-sm-4,.col-sm-5,.col-sm-6,.col-sm-7,.col-sm-8,.col-sm-9{float:left}.col-sm-12{width:100%}.col-sm-11{width:91.66666667%}.col-sm-10{width:83.33333333%}.col-sm-9{width:75%}.col-sm-8{width:66.66666667%}.col-sm-7{width:58.33333333%}.col-sm-6{width:50%}.col-sm-5{width:41.66666667%}.col-sm-4{width:33.33333333%}.col-sm-3{width:25%}.col-sm-2{width:16.66666667%}.col-sm-1{width:8.33333333%}.col-sm-pull-12{right:100%}.col-sm-pull-11{right:91.66666667%}.col-sm-pull-10{right:83.33333333%}.col-sm-pull-9{right:75%}.col-sm-pull-8{right:66.66666667%}.col-sm-pull-7{right:58.33333333%}.col-sm-pull-6{right:50%}.col-sm-pull-5{right:41.66666667%}.col-sm-pull-4{right:33.33333333%}.col-sm-pull-3{right:25%}.col-sm-pull-2{right:16.66666667%}.col-sm-pull-1{right:8.33333333%}.col-sm-pull-0{right:auto}.col-sm-push-12{left:100%}.col-sm-push-11{left:91.66666667%}.col-sm-push-10{left:83.33333333%}.col-sm-push-9{left:75%}.col-sm-push-8{left:66.66666667%}.col-sm-push-7{left:58.33333333%}.col-sm-push-6{left:50%}.col-sm-push-5{left:41.66666667%}.col-sm-push-4{left:33.33333333%}.col-sm-push-3{left:25%}.col-sm-push-2{left:16.66666667%}.col-sm-push-1{left:8.33333333%}.col-sm-push-0{left:auto}.col-sm-offset-12{margin-left:100%}.col-sm-offset-11{margin-left:91.66666667%}.col-sm-offset-10{margin-left:83.33333333%}.col-sm-offset-9{margin-left:75%}.col-sm-offset-8{margin-left:66.66666667%}.col-sm-offset-7{margin-left:58.33333333%}.col-sm-offset-6{margin-left:50%}.col-sm-offset-5{margin-left:41.66666667%}.col-sm-offset-4{margin-left:33.33333333%}.col-sm-offset-3{margin-left:25%}.col-sm-offset-2{margin-left:16.66666667%}.col-sm-offset-1{margin-left:8.33333333%}.col-sm-offset-0{margin-left:0}}@media (min-width:992px){.col-md-1,.col-md-10,.col-md-11,.col-md-12,.col-md-2,.col-md-3,.col-md-4,.col-md-5,.col-md-6,.col-md-7,.col-md-8,.col-md-9{float:left}.col-md-12{width:100%}.col-md-11{width:91.66666667%}.col-md-10{width:83.33333333%}.col-md-9{width:75%}.col-md-8{width:66.66666667%}.col-md-7{width:58.33333333%}.col-md-6{width:50%}.col-md-5{width:41.66666667%}.col-md-4{width:33.33333333%}.col-md-3{width:25%}.col-md-2{width:16.66666667%}.col-md-1{width:8.33333333%}.col-md-pull-12{right:100%}.col-md-pull-11{right:91.66666667%}.col-md-pull-10{right:83.33333333%}.col-md-pull-9{right:75%}.col-md-pull-8{right:66.66666667%}.col-md-pull-7{right:58.33333333%}.col-md-pull-6{right:50%}.col-md-pull-5{right:41.66666667%}.col-md-pull-4{right:33.33333333%}.col-md-pull-3{right:25%}.col-md-pull-2{right:16.66666667%}.col-md-pull-1{right:8.33333333%}.col-md-pull-0{right:auto}.col-md-push-12{left:100%}.col-md-push-11{left:91.66666667%}.col-md-push-10{left:83.33333333%}.col-md-push-9{left:75%}.col-md-push-8{left:66.66666667%}.col-md-push-7{left:58.33333333%}.col-md-push-6{left:50%}.col-md-push-5{left:41.66666667%}.col-md-push-4{left:33.33333333%}.col-md-push-3{left:25%}.col-md-push-2{left:16.66666667%}.col-md-push-1{left:8.33333333%}.col-md-push-0{left:auto}.col-md-offset-12{margin-left:100%}.col-md-offset-11{margin-left:91.66666667%}.col-md-offset-10{margin-left:83.33333333%}.col-md-offset-9{margin-left:75%}.col-md-offset-8{margin-left:66.66666667%}.col-md-offset-7{margin-left:58.33333333%}.col-md-offset-6{margin-left:50%}.col-md-offset-5{margin-left:41.66666667%}.col-md-offset-4{margin-left:33.33333333%}.col-md-offset-3{margin-left:25%}.col-md-offset-2{margin-left:16.66666667%}.col-md-offset-1{margin-left:8.33333333%}.col-md-offset-0{margin-left:0}}@media (min-width:1200px){.col-lg-1,.col-lg-10,.col-lg-11,.col-lg-12,.col-lg-2,.col-lg-3,.col-lg-4,.col-lg-5,.col-lg-6,.col-lg-7,.col-lg-8,.col-lg-9{float:left}.col-lg-12{width:100%}.col-lg-11{width:91.66666667%}.col-lg-10{width:83.33333333%}.col-lg-9{width:75%}.col-lg-8{width:66.66666667%}.col-lg-7{width:58.33333333%}.col-lg-6{width:50%}.col-lg-5{width:41.66666667%}.col-lg-4{width:33.33333333%}.col-lg-3{width:25%}.col-lg-2{width:16.66666667%}.col-lg-1{width:8.33333333%}.col-lg-pull-12{right:100%}.col-lg-pull-11{right:91.66666667%}.col-lg-pull-10{right:83.33333333%}.col-lg-pull-9{right:75%}.col-lg-pull-8{right:66.66666667%}.col-lg-pull-7{right:58.33333333%}.col-lg-pull-6{right:50%}.col-lg-pull-5{right:41.66666667%}.col-lg-pull-4{right:33.33333333%}.col-lg-pull-3{right:25%}.col-lg-pull-2{right:16.66666667%}.col-lg-pull-1{right:8.33333333%}.col-lg-pull-0{right:auto}.col-lg-push-12{left:100%}.col-lg-push-11{left:91.66666667%}.col-lg-push-10{left:83.33333333%}.col-lg-push-9{left:75%}.col-lg-push-8{left:66.66666667%}.col-lg-push-7{left:58.33333333%}.col-lg-push-6{left:50%}.col-lg-push-5{left:41.66666667%}.col-lg-push-4{left:33.33333333%}.col-lg-push-3{left:25%}.col-lg-push-2{left:16.66666667%}.col-lg-push-1{left:8.33333333%}.col-lg-push-0{left:auto}.col-lg-offset-12{margin-left:100%}.col-lg-offset-11{margin-left:91.66666667%}.col-lg-offset-10{margin-left:83.33333333%}.col-lg-offset-9{margin-left:75%}.col-lg-offset-8{margin-left:66.66666667%}.col-lg-offset-7{margin-left:58.33333333%}.col-lg-offset-6{margin-left:50%}.col-lg-offset-5{margin-left:41.66666667%}.col-lg-offset-4{margin-left:33.33333333%}.col-lg-offset-3{margin-left:25%}.col-lg-offset-2{margin-left:16.66666667%}.col-lg-offset-1{margin-left:8.33333333%}.col-lg-offset-0{margin-left:0}}table{background-color:transparent}caption{padding-top:8px;padding-bottom:8px;color:#777;text-align:left}th{text-align:left}.table{width:100%;max-width:100%;margin-bottom:20px}.table>tbody>tr>td,.table>tbody>tr>th,.table>tfoot>tr>td,.table>tfoot>tr>th,.table>thead>tr>td,.table>thead>tr>th{padding:8px;line-height:1.42857143;vertical-align:top;border-top:1px solid #ddd}.table>thead>tr>th{vertical-align:bottom;border-bottom:2px solid #ddd}.table>caption+thead>tr:first-child>td,.table>caption+thead>tr:first-child>th,.table>colgroup+thead>tr:first-child>td,.table>colgroup+thead>tr:first-child>th,.table>thead:first-child>tr:first-child>td,.table>thead:first-child>tr:first-child>th{border-top:0}.table>tbody+tbody{border-top:2px solid #ddd}.table .table{background-color:#fff}.table-condensed>tbody>tr>td,.table-condensed>tbody>tr>th,.table-condensed>tfoot>tr>td,.table-condensed>tfoot>tr>th,.table-condensed>thead>tr>td,.table-condensed>thead>tr>th{padding:5px}.table-bordered{border:1px solid #ddd}.table-bordered>tbody>tr>td,.table-bordered>tbody>tr>th,.table-bordered>tfoot>tr>td,.table-bordered>tfoot>tr>th,.table-bordered>thead>tr>td,.table-bordered>thead>tr>th{border:1px solid #ddd}.table-bordered>thead>tr>td,.table-bordered>thead>tr>th{border-bottom-width:2px}.table-striped>tbody>tr:nth-of-type(odd){background-color:#f9f9f9}.table-hover>tbody>tr:hover{background-color:#f5f5f5}table col[class*=col-]{position:static;display:table-column;float:none}table td[class*=col-],table th[class*=col-]{position:static;display:table-cell;float:none}.table>tbody>tr.active>td,.table>tbody>tr.active>th,.table>tbody>tr>td.active,.table>tbody>tr>th.active,.table>tfoot>tr.active>td,.table>tfoot>tr.active>th,.table>tfoot>tr>td.active,.table>tfoot>tr>th.active,.table>thead>tr.active>td,.table>thead>tr.active>th,.table>thead>tr>td.active,.table>thead>tr>th.active{background-color:#f5f5f5}.table-hover>tbody>tr.active:hover>td,.table-hover>tbody>tr.active:hover>th,.table-hover>tbody>tr:hover>.active,.table-hover>tbody>tr>td.active:hover,.table-hover>tbody>tr>th.active:hover{background-color:#e8e8e8}.table>tbody>tr.success>td,.table>tbody>tr.success>th,.table>tbody>tr>td.success,.table>tbody>tr>th.success,.table>tfoot>tr.success>td,.table>tfoot>tr.success>th,.table>tfoot>tr>td.success,.table>tfoot>tr>th.success,.table>thead>tr.success>td,.table>thead>tr.success>th,.table>thead>tr>td.success,.table>thead>tr>th.success{background-color:#dff0d8}.table-hover>tbody>tr.success:hover>td,.table-hover>tbody>tr.success:hover>th,.table-hover>tbody>tr:hover>.success,.table-hover>tbody>tr>td.success:hover,.table-hover>tbody>tr>th.success:hover{background-color:#d0e9c6}.table>tbody>tr.info>td,.table>tbody>tr.info>th,.table>tbody>tr>td.info,.table>tbody>tr>th.info,.table>tfoot>tr.info>td,.table>tfoot>tr.info>th,.table>tfoot>tr>td.info,.table>tfoot>tr>th.info,.table>thead>tr.info>td,.table>thead>tr.info>th,.table>thead>tr>td.info,.table>thead>tr>th.info{background-color:#d9edf7}.table-hover>tbody>tr.info:hover>td,.table-hover>tbody>tr.info:hover>th,.table-hover>tbody>tr:hover>.info,.table-hover>tbody>tr>td.info:hover,.table-hover>tbody>tr>th.info:hover{background-color:#c4e3f3}.table>tbody>tr.warning>td,.table>tbody>tr.warning>th,.table>tbody>tr>td.warning,.table>tbody>tr>th.warning,.table>tfoot>tr.warning>td,.table>tfoot>tr.warning>th,.table>tfoot>tr>td.warning,.table>tfoot>tr>th.warning,.table>thead>tr.warning>td,.table>thead>tr.warning>th,.table>thead>tr>td.warning,.table>thead>tr>th.warning{background-color:#fcf8e3}.table-hover>tbody>tr.warning:hover>td,.table-hover>tbody>tr.warning:hover>th,.table-hover>tbody>tr:hover>.warning,.table-hover>tbody>tr>td.warning:hover,.table-hover>tbody>tr>th.warning:hover{background-color:#faf2cc}.table>tbody>tr.danger>td,.table>tbody>tr.danger>th,.table>tbody>tr>td.danger,.table>tbody>tr>th.danger,.table>tfoot>tr.danger>td,.table>tfoot>tr.danger>th,.table>tfoot>tr>td.danger,.table>tfoot>tr>th.danger,.table>thead>tr.danger>td,.table>thead>tr.danger>th,.table>thead>tr>td.danger,.table>thead>tr>th.danger{background-color:#f2dede}.table-hover>tbody>tr.danger:hover>td,.table-hover>tbody>tr.danger:hover>th,.table-hover>tbody>tr:hover>.danger,.table-hover>tbody>tr>td.danger:hover,.table-hover>tbody>tr>th.danger:hover{background-color:#ebcccc}.table-responsive{min-height:.01%;overflow-x:auto}@media screen and (max-width:767px){.table-responsive{width:100%;margin-bottom:15px;overflow-y:hidden;-ms-overflow-style:-ms-autohiding-scrollbar;border:1px solid #ddd}.table-responsive>.table{margin-bottom:0}.table-responsive>.table>tbody>tr>td,.table-responsive>.table>tbody>tr>th,.table-responsive>.table>tfoot>tr>td,.table-responsive>.table>tfoot>tr>th,.table-responsive>.table>thead>tr>td,.table-responsive>.table>thead>tr>th{white-space:nowrap}.table-responsive>.table-bordered{border:0}.table-responsive>.table-bordered>tbody>tr>td:first-child,.table-responsive>.table-bordered>tbody>tr>th:first-child,.table-responsive>.table-bordered>tfoot>tr>td:first-child,.table-responsive>.table-bordered>tfoot>tr>th:first-child,.table-responsive>.table-bordered>thead>tr>td:first-child,.table-responsive>.table-bordered>thead>tr>th:first-child{border-left:0}.table-responsive>.table-bordered>tbody>tr>td:last-child,.table-responsive>.table-bordered>tbody>tr>th:last-child,.table-responsive>.table-bordered>tfoot>tr>td:last-child,.table-responsive>.table-bordered>tfoot>tr>th:last-child,.table-responsive>.table-bordered>thead>tr>td:last-child,.table-responsive>.table-bordered>thead>tr>th:last-child{border-right:0}.table-responsive>.table-bordered>tbody>tr:last-child>td,.table-responsive>.table-bordered>tbody>tr:last-child>th,.table-responsive>.table-bordered>tfoot>tr:last-child>td,.table-responsive>.table-bordered>tfoot>tr:last-child>th{border-bottom:0}}fieldset{min-width:0;padding:0;margin:0;border:0}legend{display:block;width:100%;padding:0;margin-bottom:20px;font-size:21px;line-height:inherit;color:#333;border:0;border-bottom:1px solid #e5e5e5}label{display:inline-block;max-width:100%;margin-bottom:5px;font-weight:700}input[type=search]{-webkit-box-sizing:border-box;-moz-box-sizing:border-box;box-sizing:border-box}input[type=checkbox],input[type=radio]{margin:4px 0 0;line-height:normal}input[type=file]{display:block}input[type=range]{display:block;width:100%}select[multiple],select[size]{height:auto}input[type=checkbox]:focus,input[type=file]:focus,input[type=radio]:focus{outline:5px auto -webkit-focus-ring-color;outline-offset:-2px}output{display:block;padding-top:7px;font-size:14px;line-height:1.42857143;color:#555}.form-control{display:block;width:100%;height:34px;padding:6px 12px;font-size:14px;line-height:1.42857143;color:#555;background-color:#fff;background-image:none;border:1px solid #ccc;border-radius:4px;-webkit-box-shadow:inset 0 1px 1px rgba(0,0,0,.075);box-shadow:inset 0 1px 1px rgba(0,0,0,.075);-webkit-transition:border-color ease-in-out .15s,-webkit-box-shadow ease-in-out .15s;-o-transition:border-color ease-in-out .15s,box-shadow ease-in-out .15s;transition:border-color ease-in-out .15s,box-shadow ease-in-out .15s}.form-control:focus{border-color:#66afe9;outline:0;-webkit-box-shadow:inset 0 1px 1px rgba(0,0,0,.075),0 0 8px rgba(102,175,233,.6);box-shadow:inset 0 1px 1px rgba(0,0,0,.075),0 0 8px rgba(102,175,233,.6)}.form-control::-moz-placeholder{color:#999;opacity:1}.form-control:-ms-input-placeholder{color:#999}.form-control::-webkit-input-placeholder{color:#999}.form-control::-ms-expand{background-color:transparent;border:0}.form-control[disabled],.form-control[readonly],fieldset[disabled] .form-control{background-color:#eee;opacity:1}.form-control[disabled],fieldset[disabled] .form-control{cursor:not-allowed}textarea.form-control{height:auto}input[type=search]{-webkit-appearance:none}@media screen and (-webkit-min-device-pixel-ratio:0){input[type=date].form-control,input[type=datetime-local].form-control,input[type=month].form-control,input[type=time].form-control{line-height:34px}.input-group-sm input[type=date],.input-group-sm input[type=datetime-local],.input-group-sm input[type=month],.input-group-sm input[type=time],input[type=date].input-sm,input[type=datetime-local].input-sm,input[type=month].input-sm,input[type=time].input-sm{line-height:30px}.input-group-lg input[type=date],.input-group-lg input[type=datetime-local],.input-group-lg input[type=month],.input-group-lg input[type=time],input[type=date].input-lg,input[type=datetime-local].input-lg,input[type=month].input-lg,input[type=time].input-lg{line-height:46px}}.form-group{margin-bottom:15px}.checkbox,.radio{position:relative;display:block;margin-top:10px;margin-bottom:10px}.checkbox label,.radio label{min-height:20px;padding-left:20px;margin-bottom:0;font-weight:400;cursor:pointer}.checkbox input[type=checkbox],.checkbox-inline input[type=checkbox],.radio input[type=radio],.radio-inline input[type=radio]{position:absolute;margin-left:-20px}.checkbox+.checkbox,.radio+.radio{margin-top:-5px}.checkbox-inline,.radio-inline{position:relative;display:inline-block;padding-left:20px;margin-bottom:0;font-weight:400;vertical-align:middle;cursor:pointer}.checkbox-inline+.checkbox-inline,.radio-inline+.radio-inline{margin-top:0;margin-left:10px}fieldset[disabled] input[type=checkbox],fieldset[disabled] input[type=radio],input[type=checkbox].disabled,input[type=checkbox][disabled],input[type=radio].disabled,input[type=radio][disabled]{cursor:not-allowed}.checkbox-inline.disabled,.radio-inline.disabled,fieldset[disabled] .checkbox-inline,fieldset[disabled] .radio-inline{cursor:not-allowed}.checkbox.disabled label,.radio.disabled label,fieldset[disabled] .checkbox label,fieldset[disabled] .radio label{cursor:not-allowed}.form-control-static{min-height:34px;padding-top:7px;padding-bottom:7px;margin-bottom:0}.form-control-static.input-lg,.form-control-static.input-sm{padding-right:0;padding-left:0}.input-sm{height:30px;padding:5px 10px;font-size:12px;line-height:1.5;border-radius:3px}select.input-sm{height:30px;line-height:30px}select[multiple].input-sm,textarea.input-sm{height:auto}.form-group-sm .form-control{height:30px;padding:5px 10px;font-size:12px;line-height:1.5;border-radius:3px}.form-group-sm select.form-control{height:30px;line-height:30px}.form-group-sm select[multiple].form-control,.form-group-sm textarea.form-control{height:auto}.form-group-sm .form-control-static{height:30px;min-height:32px;padding:6px 10px;font-size:12px;line-height:1.5}.input-lg{height:46px;padding:10px 16px;font-size:18px;line-height:1.3333333;border-radius:6px}select.input-lg{height:46px;line-height:46px}select[multiple].input-lg,textarea.input-lg{height:auto}.form-group-lg .form-control{height:46px;padding:10px 16px;font-size:18px;line-height:1.3333333;border-radius:6px}.form-group-lg select.form-control{height:46px;line-height:46px}.form-group-lg select[multiple].form-control,.form-group-lg textarea.form-control{height:auto}.form-group-lg .form-control-static{height:46px;min-height:38px;padding:11px 16px;font-size:18px;line-height:1.3333333}.has-feedback{position:relative}.has-feedback .form-control{padding-right:42.5px}.form-control-feedback{position:absolute;top:0;right:0;z-index:2;display:block;width:34px;height:34px;line-height:34px;text-align:center;pointer-events:none}.form-group-lg .form-control+.form-control-feedback,.input-group-lg+.form-control-feedback,.input-lg+.form-control-feedback{width:46px;height:46px;line-height:46px}.form-group-sm .form-control+.form-control-feedback,.input-group-sm+.form-control-feedback,.input-sm+.form-control-feedback{width:30px;height:30px;line-height:30px}.has-success .checkbox,.has-success .checkbox-inline,.has-success .control-label,.has-success .help-block,.has-success .radio,.has-success .radio-inline,.has-success.checkbox label,.has-success.checkbox-inline label,.has-success.radio label,.has-success.radio-inline label{color:#3c763d}.has-success .form-control{border-color:#3c763d;-webkit-box-shadow:inset 0 1px 1px rgba(0,0,0,.075);box-shadow:inset 0 1px 1px rgba(0,0,0,.075)}.has-success .form-control:focus{border-color:#2b542c;-webkit-box-shadow:inset 0 1px 1px rgba(0,0,0,.075),0 0 6px #67b168;box-shadow:inset 0 1px 1px rgba(0,0,0,.075),0 0 6px #67b168}.has-success .input-group-addon{color:#3c763d;background-color:#dff0d8;border-color:#3c763d}.has-success .form-control-feedback{color:#3c763d}.has-warning .checkbox,.has-warning .checkbox-inline,.has-warning .control-label,.has-warning .help-block,.has-warning .radio,.has-warning .radio-inline,.has-warning.checkbox label,.has-warning.checkbox-inline label,.has-warning.radio label,.has-warning.radio-inline label{color:#8a6d3b}.has-warning .form-control{border-color:#8a6d3b;-webkit-box-shadow:inset 0 1px 1px rgba(0,0,0,.075);box-shadow:inset 0 1px 1px rgba(0,0,0,.075)}.has-warning .form-control:focus{border-color:#66512c;-webkit-box-shadow:inset 0 1px 1px rgba(0,0,0,.075),0 0 6px #c0a16b;box-shadow:inset 0 1px 1px rgba(0,0,0,.075),0 0 6px #c0a16b}.has-warning .input-group-addon{color:#8a6d3b;background-color:#fcf8e3;border-color:#8a6d3b}.has-warning .form-control-feedback{color:#8a6d3b}.has-error .checkbox,.has-error .checkbox-inline,.has-error .control-label,.has-error .help-block,.has-error .radio,.has-error .radio-inline,.has-error.checkbox label,.has-error.checkbox-inline label,.has-error.radio label,.has-error.radio-inline label{color:#a94442}.has-error .form-control{border-color:#a94442;-webkit-box-shadow:inset 0 1px 1px rgba(0,0,0,.075);box-shadow:inset 0 1px 1px rgba(0,0,0,.075)}.has-error .form-control:focus{border-color:#843534;-webkit-box-shadow:inset 0 1px 1px rgba(0,0,0,.075),0 0 6px #ce8483;box-shadow:inset 0 1px 1px rgba(0,0,0,.075),0 0 6px #ce8483}.has-error .input-group-addon{color:#a94442;background-color:#f2dede;border-color:#a94442}.has-error .form-control-feedback{color:#a94442}.has-feedback label~.form-control-feedback{top:25px}.has-feedback label.sr-only~.form-control-feedback{top:0}.help-block{display:block;margin-top:5px;margin-bottom:10px;color:#737373}@media (min-width:768px){.form-inline .form-group{display:inline-block;margin-bottom:0;vertical-align:middle}.form-inline .form-control{display:inline-block;width:auto;vertical-align:middle}.form-inline .form-control-static{display:inline-block}.form-inline .input-group{display:inline-table;vertical-align:middle}.form-inline .input-group .form-control,.form-inline .input-group .input-group-addon,.form-inline .input-group .input-group-btn{width:auto}.form-inline .input-group>.form-control{width:100%}.form-inline .control-label{margin-bottom:0;vertical-align:middle}.form-inline .checkbox,.form-inline .radio{display:inline-block;margin-top:0;margin-bottom:0;vertical-align:middle}.form-inline .checkbox label,.form-inline .radio label{padding-left:0}.form-inline .checkbox input[type=checkbox],.form-inline .radio input[type=radio]{position:relative;margin-left:0}.form-inline .has-feedback .form-control-feedback{top:0}}.form-horizontal .checkbox,.form-horizontal .checkbox-inline,.form-horizontal .radio,.form-horizontal .radio-inline{padding-top:7px;margin-top:0;margin-bottom:0}.form-horizontal .checkbox,.form-horizontal .radio{min-height:27px}.form-horizontal .form-group{margin-right:-15px;margin-left:-15px}@media (min-width:768px){.form-horizontal .control-label{padding-top:7px;margin-bottom:0;text-align:right}}.form-horizontal .has-feedback .form-control-feedback{right:15px}@media (min-width:768px){.form-horizontal .form-group-lg .control-label{padding-top:11px;font-size:18px}}@media (min-width:768px){.form-horizontal .form-group-sm .control-label{padding-top:6px;font-size:12px}}.btn{display:inline-block;padding:6px 12px;margin-bottom:0;font-size:14px;font-weight:400;line-height:1.42857143;text-align:center;white-space:nowrap;vertical-align:middle;-ms-touch-action:manipulation;touch-action:manipulation;cursor:pointer;-webkit-user-select:none;-moz-user-select:none;-ms-user-select:none;user-select:none;background-image:none;border:1px solid transparent;border-radius:4px}.btn.active.focus,.btn.active:focus,.btn.focus,.btn:active.focus,.btn:active:focus,.btn:focus{outline:5px auto -webkit-focus-ring-color;outline-offset:-2px}.btn.focus,.btn:focus,.btn:hover{color:#333;text-decoration:none}.btn.active,.btn:active{background-image:none;outline:0;-webkit-box-shadow:inset 0 3px 5px rgba(0,0,0,.125);box-shadow:inset 0 3px 5px rgba(0,0,0,.125)}.btn.disabled,.btn[disabled],fieldset[disabled] .btn{cursor:not-allowed;-webkit-box-shadow:none;box-shadow:none;opacity:.65}a.btn.disabled,fieldset[disabled] a.btn{pointer-events:none}.btn-default{color:#333;background-color:#fff;border-color:#ccc}.btn-default.focus,.btn-default:focus{color:#333;background-color:#e6e6e6;border-color:#8c8c8c}.btn-default:hover{color:#333;background-color:#e6e6e6;border-color:#adadad}.btn-default.active,.btn-default:active,.open>.dropdown-toggle.btn-default{color:#333;background-color:#e6e6e6;border-color:#adadad}.btn-default.active.focus,.btn-default.active:focus,.btn-default.active:hover,.btn-default:active.focus,.btn-default:active:focus,.btn-default:active:hover,.open>.dropdown-toggle.btn-default.focus,.open>.dropdown-toggle.btn-default:focus,.open>.dropdown-toggle.btn-default:hover{color:#333;background-color:#d4d4d4;border-color:#8c8c8c}.btn-default.active,.btn-default:active,.open>.dropdown-toggle.btn-default{background-image:none}.btn-default.disabled.focus,.btn-default.disabled:focus,.btn-default.disabled:hover,.btn-default[disabled].focus,.btn-default[disabled]:focus,.btn-default[disabled]:hover,fieldset[disabled] .btn-default.focus,fieldset[disabled] .btn-default:focus,fieldset[disabled] .btn-default:hover{background-color:#fff;border-color:#ccc}.btn-default .badge{color:#fff;background-color:#333}.btn-primary{color:#fff;background-color:#337ab7;border-color:#2e6da4}.btn-primary.focus,.btn-primary:focus{color:#fff;background-color:#286090;border-color:#122b40}.btn-primary:hover{color:#fff;background-color:#286090;border-color:#204d74}.btn-primary.active,.btn-primary:active,.open>.dropdown-toggle.btn-primary{color:#fff;background-color:#286090;border-color:#204d74}.btn-primary.active.focus,.btn-primary.active:focus,.btn-primary.active:hover,.btn-primary:active.focus,.btn-primary:active:focus,.btn-primary:active:hover,.open>.dropdown-toggle.btn-primary.focus,.open>.dropdown-toggle.btn-primary:focus,.open>.dropdown-toggle.btn-primary:hover{color:#fff;background-color:#204d74;border-color:#122b40}.btn-primary.active,.btn-primary:active,.open>.dropdown-toggle.btn-primary{background-image:none}.btn-primary.disabled.focus,.btn-primary.disabled:focus,.btn-primary.disabled:hover,.btn-primary[disabled].focus,.btn-primary[disabled]:focus,.btn-primary[disabled]:hover,fieldset[disabled] .btn-primary.focus,fieldset[disabled] .btn-primary:focus,fieldset[disabled] .btn-primary:hover{background-color:#337ab7;border-color:#2e6da4}.btn-primary .badge{color:#337ab7;background-color:#fff}.btn-success{color:#fff;background-color:#5cb85c;border-color:#4cae4c}.btn-success.focus,.btn-success:focus{color:#fff;background-color:#449d44;border-color:#255625}.btn-success:hover{color:#fff;background-color:#449d44;border-color:#398439}.btn-success.active,.btn-success:active,.open>.dropdown-toggle.btn-success{color:#fff;background-color:#449d44;border-color:#398439}.btn-success.active.focus,.btn-success.active:focus,.btn-success.active:hover,.btn-success:active.focus,.btn-success:active:focus,.btn-success:active:hover,.open>.dropdown-toggle.btn-success.focus,.open>.dropdown-toggle.btn-success:focus,.open>.dropdown-toggle.btn-success:hover{color:#fff;background-color:#398439;border-color:#255625}.btn-success.active,.btn-success:active,.open>.dropdown-toggle.btn-success{background-image:none}.btn-success.disabled.focus,.btn-success.disabled:focus,.btn-success.disabled:hover,.btn-success[disabled].focus,.btn-success[disabled]:focus,.btn-success[disabled]:hover,fieldset[disabled] .btn-success.focus,fieldset[disabled] .btn-success:focus,fieldset[disabled] .btn-success:hover{background-color:#5cb85c;border-color:#4cae4c}.btn-success .badge{color:#5cb85c;background-color:#fff}.btn-info{color:#fff;background-color:#5bc0de;border-color:#46b8da}.btn-info.focus,.btn-info:focus{color:#fff;background-color:#31b0d5;border-color:#1b6d85}.btn-info:hover{color:#fff;background-color:#31b0d5;border-color:#269abc}.btn-info.active,.btn-info:active,.open>.dropdown-toggle.btn-info{color:#fff;background-color:#31b0d5;border-color:#269abc}.btn-info.active.focus,.btn-info.active:focus,.btn-info.active:hover,.btn-info:active.focus,.btn-info:active:focus,.btn-info:active:hover,.open>.dropdown-toggle.btn-info.focus,.open>.dropdown-toggle.btn-info:focus,.open>.dropdown-toggle.btn-info:hover{color:#fff;background-color:#269abc;border-color:#1b6d85}.btn-info.active,.btn-info:active,.open>.dropdown-toggle.btn-info{background-image:none}.btn-info.disabled.focus,.btn-info.disabled:focus,.btn-info.disabled:hover,.btn-info[disabled].focus,.btn-info[disabled]:focus,.btn-info[disabled]:hover,fieldset[disabled] .btn-info.focus,fieldset[disabled] .btn-info:focus,fieldset[disabled] .btn-info:hover{background-color:#5bc0de;border-color:#46b8da}.btn-info .badge{color:#5bc0de;background-color:#fff}.btn-warning{color:#fff;background-color:#f0ad4e;border-color:#eea236}.btn-warning.focus,.btn-warning:focus{color:#fff;background-color:#ec971f;border-color:#985f0d}.btn-warning:hover{color:#fff;background-color:#ec971f;border-color:#d58512}.btn-warning.active,.btn-warning:active,.open>.dropdown-toggle.btn-warning{color:#fff;background-color:#ec971f;border-color:#d58512}.btn-warning.active.focus,.btn-warning.active:focus,.btn-warning.active:hover,.btn-warning:active.focus,.btn-warning:active:focus,.btn-warning:active:hover,.open>.dropdown-toggle.btn-warning.focus,.open>.dropdown-toggle.btn-warning:focus,.open>.dropdown-toggle.btn-warning:hover{color:#fff;background-color:#d58512;border-color:#985f0d}.btn-warning.active,.btn-warning:active,.open>.dropdown-toggle.btn-warning{background-image:none}.btn-warning.disabled.focus,.btn-warning.disabled:focus,.btn-warning.disabled:hover,.btn-warning[disabled].focus,.btn-warning[disabled]:focus,.btn-warning[disabled]:hover,fieldset[disabled] .btn-warning.focus,fieldset[disabled] .btn-warning:focus,fieldset[disabled] .btn-warning:hover{background-color:#f0ad4e;border-color:#eea236}.btn-warning .badge{color:#f0ad4e;background-color:#fff}.btn-danger{color:#fff;background-color:#d9534f;border-color:#d43f3a}.btn-danger.focus,.btn-danger:focus{color:#fff;background-color:#c9302c;border-color:#761c19}.btn-danger:hover{color:#fff;background-color:#c9302c;border-color:#ac2925}.btn-danger.active,.btn-danger:active,.open>.dropdown-toggle.btn-danger{color:#fff;background-color:#c9302c;border-color:#ac2925}.btn-danger.active.focus,.btn-danger.active:focus,.btn-danger.active:hover,.btn-danger:active.focus,.btn-danger:active:focus,.btn-danger:active:hover,.open>.dropdown-toggle.btn-danger.focus,.open>.dropdown-toggle.btn-danger:focus,.open>.dropdown-toggle.btn-danger:hover{color:#fff;background-color:#ac2925;border-color:#761c19}.btn-danger.active,.btn-danger:active,.open>.dropdown-toggle.btn-danger{background-image:none}.btn-danger.disabled.focus,.btn-danger.disabled:focus,.btn-danger.disabled:hover,.btn-danger[disabled].focus,.btn-danger[disabled]:focus,.btn-danger[disabled]:hover,fieldset[disabled] .btn-danger.focus,fieldset[disabled] .btn-danger:focus,fieldset[disabled] .btn-danger:hover{background-color:#d9534f;border-color:#d43f3a}.btn-danger .badge{color:#d9534f;background-color:#fff}.btn-link{font-weight:400;color:#337ab7;border-radius:0}.btn-link,.btn-link.active,.btn-link:active,.btn-link[disabled],fieldset[disabled] .btn-link{background-color:transparent;-webkit-box-shadow:none;box-shadow:none}.btn-link,.btn-link:active,.btn-link:focus,.btn-link:hover{border-color:transparent}.btn-link:focus,.btn-link:hover{color:#23527c;text-decoration:underline;background-color:transparent}.btn-link[disabled]:focus,.btn-link[disabled]:hover,fieldset[disabled] .btn-link:focus,fieldset[disabled] .btn-link:hover{color:#777;text-decoration:none}.btn-group-lg>.btn,.btn-lg{padding:10px 16px;font-size:18px;line-height:1.3333333;border-radius:6px}.btn-group-sm>.btn,.btn-sm{padding:5px 10px;font-size:12px;line-height:1.5;border-radius:3px}.btn-group-xs>.btn,.btn-xs{padding:1px 5px;font-size:12px;line-height:1.5;border-radius:3px}.btn-block{display:block;width:100%}.btn-block+.btn-block{margin-top:5px}input[type=button].btn-block,input[type=reset].btn-block,input[type=submit].btn-block{width:100%}.fade{opacity:0;-webkit-transition:opacity .15s linear;-o-transition:opacity .15s linear;transition:opacity .15s linear}.fade.in{opacity:1}.collapse{display:none}.collapse.in{display:block}tr.collapse.in{display:table-row}tbody.collapse.in{display:table-row-group}.collapsing{position:relative;height:0;overflow:hidden;-webkit-transition-timing-function:ease;-o-transition-timing-function:ease;transition-timing-function:ease;-webkit-transition-duration:.35s;-o-transition-duration:.35s;transition-duration:.35s;-webkit-transition-property:height,visibility;-o-transition-property:height,visibility;transition-property:height,visibility}.caret{display:inline-block;width:0;height:0;margin-left:2px;vertical-align:middle;border-top:4px dashed;border-right:4px solid transparent;border-left:4px solid transparent}.dropdown,.dropup{position:relative}.dropdown-toggle:focus{outline:0}.dropdown-menu{position:absolute;top:100%;left:0;z-index:1000;display:none;float:left;min-width:160px;padding:5px 0;margin:2px 0 0;font-size:14px;text-align:left;list-style:none;background-color:#fff;-webkit-background-clip:padding-box;background-clip:padding-box;border:1px solid #ccc;border:1px solid rgba(0,0,0,.15);border-radius:4px;-webkit-box-shadow:0 6px 12px rgba(0,0,0,.175);box-shadow:0 6px 12px rgba(0,0,0,.175)}.dropdown-menu.pull-right{right:0;left:auto}.dropdown-menu .divider{height:1px;margin:9px 0;overflow:hidden;background-color:#e5e5e5}.dropdown-menu>li>a{display:block;padding:3px 20px;clear:both;font-weight:400;line-height:1.42857143;color:#333;white-space:nowrap}.dropdown-menu>li>a:focus,.dropdown-menu>li>a:hover{color:#262626;text-decoration:none;background-color:#f5f5f5}.dropdown-menu>.active>a,.dropdown-menu>.active>a:focus,.dropdown-menu>.active>a:hover{color:#fff;text-decoration:none;background-color:#337ab7;outline:0}.dropdown-menu>.disabled>a,.dropdown-menu>.disabled>a:focus,.dropdown-menu>.disabled>a:hover{color:#777}.dropdown-menu>.disabled>a:focus,.dropdown-menu>.disabled>a:hover{text-decoration:none;cursor:not-allowed;background-color:transparent;background-image:none}.open>.dropdown-menu{display:block}.open>a{outline:0}.dropdown-menu-right{right:0;left:auto}.dropdown-menu-left{right:auto;left:0}.dropdown-header{display:block;padding:3px 20px;font-size:12px;line-height:1.42857143;color:#777;white-space:nowrap}.dropdown-backdrop{position:fixed;top:0;right:0;bottom:0;left:0;z-index:990}.pull-right>.dropdown-menu{right:0;left:auto}.dropup .caret,.navbar-fixed-bottom .dropdown .caret{content:"";border-top:0;border-bottom:4px dashed}.dropup .dropdown-menu,.navbar-fixed-bottom .dropdown .dropdown-menu{top:auto;bottom:100%;margin-bottom:2px}@media (min-width:768px){.navbar-right .dropdown-menu{right:0;left:auto}.navbar-right .dropdown-menu-left{right:auto;left:0}}.btn-group,.btn-group-vertical{position:relative;display:inline-block;vertical-align:middle}.btn-group-vertical>.btn,.btn-group>.btn{position:relative;float:left}.btn-group-vertical>.btn.active,.btn-group-vertical>.btn:active,.btn-group-vertical>.btn:focus,.btn-group-vertical>.btn:hover,.btn-group>.btn.active,.btn-group>.btn:active,.btn-group>.btn:focus,.btn-group>.btn:hover{z-index:2}.btn-group .btn+.btn,.btn-group .btn+.btn-group,.btn-group .btn-group+.btn,.btn-group .btn-group+.btn-group{margin-left:-1px}.btn-toolbar{margin-left:-5px}.btn-toolbar .btn,.btn-toolbar .btn-group,.btn-toolbar .input-group{float:left}.btn-toolbar>.btn,.btn-toolbar>.btn-group,.btn-toolbar>.input-group{margin-left:5px}.btn-group>.btn:not(:first-child):not(:last-child):not(.dropdown-toggle){border-radius:0}.btn-group>.btn:first-child{margin-left:0}.btn-group>.btn:first-child:not(:last-child):not(.dropdown-toggle){border-top-right-radius:0;border-bottom-right-radius:0}.btn-group>.btn:last-child:not(:first-child),.btn-group>.dropdown-toggle:not(:first-child){border-top-left-radius:0;border-bottom-left-radius:0}.btn-group>.btn-group{float:left}.btn-group>.btn-group:not(:first-child):not(:last-child)>.btn{border-radius:0}.btn-group>.btn-group:first-child:not(:last-child)>.btn:last-child,.btn-group>.btn-group:first-child:not(:last-child)>.dropdown-toggle{border-top-right-radius:0;border-bottom-right-radius:0}.btn-group>.btn-group:last-child:not(:first-child)>.btn:first-child{border-top-left-radius:0;border-bottom-left-radius:0}.btn-group .dropdown-toggle:active,.btn-group.open .dropdown-toggle{outline:0}.btn-group>.btn+.dropdown-toggle{padding-right:8px;padding-left:8px}.btn-group>.btn-lg+.dropdown-toggle{padding-right:12px;padding-left:12px}.btn-group.open .dropdown-toggle{-webkit-box-shadow:inset 0 3px 5px rgba(0,0,0,.125);box-shadow:inset 0 3px 5px rgba(0,0,0,.125)}.btn-group.open .dropdown-toggle.btn-link{-webkit-box-shadow:none;box-shadow:none}.btn .caret{margin-left:0}.btn-lg .caret{border-width:5px 5px 0;border-bottom-width:0}.dropup .btn-lg .caret{border-width:0 5px 5px}.btn-group-vertical>.btn,.btn-group-vertical>.btn-group,.btn-group-vertical>.btn-group>.btn{display:block;float:none;width:100%;max-width:100%}.btn-group-vertical>.btn-group>.btn{float:none}.btn-group-vertical>.btn+.btn,.btn-group-vertical>.btn+.btn-group,.btn-group-vertical>.btn-group+.btn,.btn-group-vertical>.btn-group+.btn-group{margin-top:-1px;margin-left:0}.btn-group-vertical>.btn:not(:first-child):not(:last-child){border-radius:0}.btn-group-vertical>.btn:first-child:not(:last-child){border-top-left-radius:4px;border-top-right-radius:4px;border-bottom-right-radius:0;border-bottom-left-radius:0}.btn-group-vertical>.btn:last-child:not(:first-child){border-top-left-radius:0;border-top-right-radius:0;border-bottom-right-radius:4px;border-bottom-left-radius:4px}.btn-group-vertical>.btn-group:not(:first-child):not(:last-child)>.btn{border-radius:0}.btn-group-vertical>.btn-group:first-child:not(:last-child)>.btn:last-child,.btn-group-vertical>.btn-group:first-child:not(:last-child)>.dropdown-toggle{border-bottom-right-radius:0;border-bottom-left-radius:0}.btn-group-vertical>.btn-group:last-child:not(:first-child)>.btn:first-child{border-top-left-radius:0;border-top-right-radius:0}.btn-group-justified{display:table;width:100%;table-layout:fixed;border-collapse:separate}.btn-group-justified>.btn,.btn-group-justified>.btn-group{display:table-cell;float:none;width:1%}.btn-group-justified>.btn-group .btn{width:100%}.btn-group-justified>.btn-group .dropdown-menu{left:auto}[data-toggle=buttons]>.btn input[type=checkbox],[data-toggle=buttons]>.btn input[type=radio],[data-toggle=buttons]>.btn-group>.btn input[type=checkbox],[data-toggle=buttons]>.btn-group>.btn input[type=radio]{position:absolute;clip:rect(0,0,0,0);pointer-events:none}.input-group{position:relative;display:table;border-collapse:separate}.input-group[class*=col-]{float:none;padding-right:0;padding-left:0}.input-group .form-control{position:relative;z-index:2;float:left;width:100%;margin-bottom:0}.input-group .form-control:focus{z-index:3}.input-group-lg>.form-control,.input-group-lg>.input-group-addon,.input-group-lg>.input-group-btn>.btn{height:46px;padding:10px 16px;font-size:18px;line-height:1.3333333;border-radius:6px}select.input-group-lg>.form-control,select.input-group-lg>.input-group-addon,select.input-group-lg>.input-group-btn>.btn{height:46px;line-height:46px}select[multiple].input-group-lg>.form-control,select[multiple].input-group-lg>.input-group-addon,select[multiple].input-group-lg>.input-group-btn>.btn,textarea.input-group-lg>.form-control,textarea.input-group-lg>.input-group-addon,textarea.input-group-lg>.input-group-btn>.btn{height:auto}.input-group-sm>.form-control,.input-group-sm>.input-group-addon,.input-group-sm>.input-group-btn>.btn{height:30px;padding:5px 10px;font-size:12px;line-height:1.5;border-radius:3px}select.input-group-sm>.form-control,select.input-group-sm>.input-group-addon,select.input-group-sm>.input-group-btn>.btn{height:30px;line-height:30px}select[multiple].input-group-sm>.form-control,select[multiple].input-group-sm>.input-group-addon,select[multiple].input-group-sm>.input-group-btn>.btn,textarea.input-group-sm>.form-control,textarea.input-group-sm>.input-group-addon,textarea.input-group-sm>.input-group-btn>.btn{height:auto}.input-group .form-control,.input-group-addon,.input-group-btn{display:table-cell}.input-group .form-control:not(:first-child):not(:last-child),.input-group-addon:not(:first-child):not(:last-child),.input-group-btn:not(:first-child):not(:last-child){border-radius:0}.input-group-addon,.input-group-btn{width:1%;white-space:nowrap;vertical-align:middle}.input-group-addon{padding:6px 12px;font-size:14px;font-weight:400;line-height:1;color:#555;text-align:center;background-color:#eee;border:1px solid #ccc;border-radius:4px}.input-group-addon.input-sm{padding:5px 10px;font-size:12px;border-radius:3px}.input-group-addon.input-lg{padding:10px 16px;font-size:18px;border-radius:6px}.input-group-addon input[type=checkbox],.input-group-addon input[type=radio]{margin-top:0}.input-group .form-control:first-child,.input-group-addon:first-child,.input-group-btn:first-child>.btn,.input-group-btn:first-child>.btn-group>.btn,.input-group-btn:first-child>.dropdown-toggle,.input-group-btn:last-child>.btn-group:not(:last-child)>.btn,.input-group-btn:last-child>.btn:not(:last-child):not(.dropdown-toggle){border-top-right-radius:0;border-bottom-right-radius:0}.input-group-addon:first-child{border-right:0}.input-group .form-control:last-child,.input-group-addon:last-child,.input-group-btn:first-child>.btn-group:not(:first-child)>.btn,.input-group-btn:first-child>.btn:not(:first-child),.input-group-btn:last-child>.btn,.input-group-btn:last-child>.btn-group>.btn,.input-group-btn:last-child>.dropdown-toggle{border-top-left-radius:0;border-bottom-left-radius:0}.input-group-addon:last-child{border-left:0}.input-group-btn{position:relative;font-size:0;white-space:nowrap}.input-group-btn>.btn{position:relative}.input-group-btn>.btn+.btn{margin-left:-1px}.input-group-btn>.btn:active,.input-group-btn>.btn:focus,.input-group-btn>.btn:hover{z-index:2}.input-group-btn:first-child>.btn,.input-group-btn:first-child>.btn-group{margin-right:-1px}.input-group-btn:last-child>.btn,.input-group-btn:last-child>.btn-group{z-index:2;margin-left:-1px}.nav{padding-left:0;margin-bottom:0;list-style:none}.nav>li{position:relative;display:block}.nav>li>a{position:relative;display:block;padding:10px 15px}.nav>li>a:focus,.nav>li>a:hover{text-decoration:none;background-color:#eee}.nav>li.disabled>a{color:#777}.nav>li.disabled>a:focus,.nav>li.disabled>a:hover{color:#777;text-decoration:none;cursor:not-allowed;background-color:transparent}.nav .open>a,.nav .open>a:focus,.nav .open>a:hover{background-color:#eee;border-color:#337ab7}.nav .nav-divider{height:1px;margin:9px 0;overflow:hidden;background-color:#e5e5e5}.nav>li>a>img{max-width:none}.nav-tabs{border-bottom:1px solid #ddd}.nav-tabs>li{float:left;margin-bottom:-1px}.nav-tabs>li>a{margin-right:2px;line-height:1.42857143;border:1px solid transparent;border-radius:4px 4px 0 0}.nav-tabs>li>a:hover{border-color:#eee #eee #ddd}.nav-tabs>li.active>a,.nav-tabs>li.active>a:focus,.nav-tabs>li.active>a:hover{color:#555;cursor:default;background-color:#fff;border:1px solid #ddd;border-bottom-color:transparent}.nav-tabs.nav-justified{width:100%;border-bottom:0}.nav-tabs.nav-justified>li{float:none}.nav-tabs.nav-justified>li>a{margin-bottom:5px;text-align:center}.nav-tabs.nav-justified>.dropdown .dropdown-menu{top:auto;left:auto}@media (min-width:768px){.nav-tabs.nav-justified>li{display:table-cell;width:1%}.nav-tabs.nav-justified>li>a{margin-bottom:0}}.nav-tabs.nav-justified>li>a{margin-right:0;border-radius:4px}.nav-tabs.nav-justified>.active>a,.nav-tabs.nav-justified>.active>a:focus,.nav-tabs.nav-justified>.active>a:hover{border:1px solid #ddd}@media (min-width:768px){.nav-tabs.nav-justified>li>a{border-bottom:1px solid #ddd;border-radius:4px 4px 0 0}.nav-tabs.nav-justified>.active>a,.nav-tabs.nav-justified>.active>a:focus,.nav-tabs.nav-justified>.active>a:hover{border-bottom-color:#fff}}.nav-pills>li{float:left}.nav-pills>li>a{border-radius:4px}.nav-pills>li+li{margin-left:2px}.nav-pills>li.active>a,.nav-pills>li.active>a:focus,.nav-pills>li.active>a:hover{color:#fff;background-color:#337ab7}.nav-stacked>li{float:none}.nav-stacked>li+li{margin-top:2px;margin-left:0}.nav-justified{width:100%}.nav-justified>li{float:none}.nav-justified>li>a{margin-bottom:5px;text-align:center}.nav-justified>.dropdown .dropdown-menu{top:auto;left:auto}@media (min-width:768px){.nav-justified>li{display:table-cell;width:1%}.nav-justified>li>a{margin-bottom:0}}.nav-tabs-justified{border-bottom:0}.nav-tabs-justified>li>a{margin-right:0;border-radius:4px}.nav-tabs-justified>.active>a,.nav-tabs-justified>.active>a:focus,.nav-tabs-justified>.active>a:hover{border:1px solid #ddd}@media (min-width:768px){.nav-tabs-justified>li>a{border-bottom:1px solid #ddd;border-radius:4px 4px 0 0}.nav-tabs-justified>.active>a,.nav-tabs-justified>.active>a:focus,.nav-tabs-justified>.active>a:hover{border-bottom-color:#fff}}.tab-content>.tab-pane{display:none}.tab-content>.active{display:block}.nav-tabs .dropdown-menu{margin-top:-1px;border-top-left-radius:0;border-top-right-radius:0}.navbar{position:relative;min-height:50px;margin-bottom:20px;border:1px solid transparent}@media (min-width:768px){.navbar{border-radius:4px}}@media (min-width:768px){.navbar-header{float:left}}.navbar-collapse{padding-right:15px;padding-left:15px;overflow-x:visible;-webkit-overflow-scrolling:touch;border-top:1px solid transparent;-webkit-box-shadow:inset 0 1px 0 rgba(255,255,255,.1);box-shadow:inset 0 1px 0 rgba(255,255,255,.1)}.navbar-collapse.in{overflow-y:auto}@media (min-width:768px){.navbar-collapse{width:auto;border-top:0;-webkit-box-shadow:none;box-shadow:none}.navbar-collapse.collapse{display:block!important;height:auto!important;padding-bottom:0;overflow:visible!important}.navbar-collapse.in{overflow-y:visible}.navbar-fixed-bottom .navbar-collapse,.navbar-fixed-top .navbar-collapse,.navbar-static-top .navbar-collapse{padding-right:0;padding-left:0}}.navbar-fixed-bottom .navbar-collapse,.navbar-fixed-top .navbar-collapse{max-height:340px}@media (max-device-width:480px) and (orientation:landscape){.navbar-fixed-bottom .navbar-collapse,.navbar-fixed-top .navbar-collapse{max-height:200px}}.container-fluid>.navbar-collapse,.container-fluid>.navbar-header,.container>.navbar-collapse,.container>.navbar-header{margin-right:-15px;margin-left:-15px}@media (min-width:768px){.container-fluid>.navbar-collapse,.container-fluid>.navbar-header,.container>.navbar-collapse,.container>.navbar-header{margin-right:0;margin-left:0}}.navbar-static-top{z-index:1000;border-width:0 0 1px}@media (min-width:768px){.navbar-static-top{border-radius:0}}.navbar-fixed-bottom,.navbar-fixed-top{position:fixed;right:0;left:0;z-index:1030}@media (min-width:768px){.navbar-fixed-bottom,.navbar-fixed-top{border-radius:0}}.navbar-fixed-top{top:0;border-width:0 0 1px}.navbar-fixed-bottom{bottom:0;margin-bottom:0;border-width:1px 0 0}.navbar-brand{float:left;height:50px;padding:15px 15px;font-size:18px;line-height:20px}.navbar-brand:focus,.navbar-brand:hover{text-decoration:none}.navbar-brand>img{display:block}@media (min-width:768px){.navbar>.container .navbar-brand,.navbar>.container-fluid .navbar-brand{margin-left:-15px}}.navbar-toggle{position:relative;float:right;padding:9px 10px;margin-top:8px;margin-right:15px;margin-bottom:8px;background-color:transparent;background-image:none;border:1px solid transparent;border-radius:4px}.navbar-toggle:focus{outline:0}.navbar-toggle .icon-bar{display:block;width:22px;height:2px;border-radius:1px}.navbar-toggle .icon-bar+.icon-bar{margin-top:4px}@media (min-width:768px){.navbar-toggle{display:none}}.navbar-nav{margin:7.5px -15px}.navbar-nav>li>a{padding-top:10px;padding-bottom:10px;line-height:20px}@media (max-width:767px){.navbar-nav .open .dropdown-menu{position:static;float:none;width:auto;margin-top:0;background-color:transparent;border:0;-webkit-box-shadow:none;box-shadow:none}.navbar-nav .open .dropdown-menu .dropdown-header,.navbar-nav .open .dropdown-menu>li>a{padding:5px 15px 5px 25px}.navbar-nav .open .dropdown-menu>li>a{line-height:20px}.navbar-nav .open .dropdown-menu>li>a:focus,.navbar-nav .open .dropdown-menu>li>a:hover{background-image:none}}@media (min-width:768px){.navbar-nav{float:left;margin:0}.navbar-nav>li{float:left}.navbar-nav>li>a{padding-top:15px;padding-bottom:15px}}.navbar-form{padding:10px 15px;margin-top:8px;margin-right:-15px;margin-bottom:8px;margin-left:-15px;border-top:1px solid transparent;border-bottom:1px solid transparent;-webkit-box-shadow:inset 0 1px 0 rgba(255,255,255,.1),0 1px 0 rgba(255,255,255,.1);box-shadow:inset 0 1px 0 rgba(255,255,255,.1),0 1px 0 rgba(255,255,255,.1)}@media (min-width:768px){.navbar-form .form-group{display:inline-block;margin-bottom:0;vertical-align:middle}.navbar-form .form-control{display:inline-block;width:auto;vertical-align:middle}.navbar-form .form-control-static{display:inline-block}.navbar-form .input-group{display:inline-table;vertical-align:middle}.navbar-form .input-group .form-control,.navbar-form .input-group .input-group-addon,.navbar-form .input-group .input-group-btn{width:auto}.navbar-form .input-group>.form-control{width:100%}.navbar-form .control-label{margin-bottom:0;vertical-align:middle}.navbar-form .checkbox,.navbar-form .radio{display:inline-block;margin-top:0;margin-bottom:0;vertical-align:middle}.navbar-form .checkbox label,.navbar-form .radio label{padding-left:0}.navbar-form .checkbox input[type=checkbox],.navbar-form .radio input[type=radio]{position:relative;margin-left:0}.navbar-form .has-feedback .form-control-feedback{top:0}}@media (max-width:767px){.navbar-form .form-group{margin-bottom:5px}.navbar-form .form-group:last-child{margin-bottom:0}}@media (min-width:768px){.navbar-form{width:auto;padding-top:0;padding-bottom:0;margin-right:0;margin-left:0;border:0;-webkit-box-shadow:none;box-shadow:none}}.navbar-nav>li>.dropdown-menu{margin-top:0;border-top-left-radius:0;border-top-right-radius:0}.navbar-fixed-bottom .navbar-nav>li>.dropdown-menu{margin-bottom:0;border-top-left-radius:4px;border-top-right-radius:4px;border-bottom-right-radius:0;border-bottom-left-radius:0}.navbar-btn{margin-top:8px;margin-bottom:8px}.navbar-btn.btn-sm{margin-top:10px;margin-bottom:10px}.navbar-btn.btn-xs{margin-top:14px;margin-bottom:14px}.navbar-text{margin-top:15px;margin-bottom:15px}@media (min-width:768px){.navbar-text{float:left;margin-right:15px;margin-left:15px}}@media (min-width:768px){.navbar-left{float:left!important}.navbar-right{float:right!important;margin-right:-15px}.navbar-right~.navbar-right{margin-right:0}}.navbar-default{background-color:#f8f8f8;border-color:#e7e7e7}.navbar-default .navbar-brand{color:#777}.navbar-default .navbar-brand:focus,.navbar-default .navbar-brand:hover{color:#5e5e5e;background-color:transparent}.navbar-default .navbar-text{color:#777}.navbar-default .navbar-nav>li>a{color:#777}.navbar-default .navbar-nav>li>a:focus,.navbar-default .navbar-nav>li>a:hover{color:#333;background-color:transparent}.navbar-default .navbar-nav>.active>a,.navbar-default .navbar-nav>.active>a:focus,.navbar-default .navbar-nav>.active>a:hover{color:#555;background-color:#e7e7e7}.navbar-default .navbar-nav>.disabled>a,.navbar-default .navbar-nav>.disabled>a:focus,.navbar-default .navbar-nav>.disabled>a:hover{color:#ccc;background-color:transparent}.navbar-default .navbar-toggle{border-color:#ddd}.navbar-default .navbar-toggle:focus,.navbar-default .navbar-toggle:hover{background-color:#ddd}.navbar-default .navbar-toggle .icon-bar{background-color:#888}.navbar-default .navbar-collapse,.navbar-default .navbar-form{border-color:#e7e7e7}.navbar-default .navbar-nav>.open>a,.navbar-default .navbar-nav>.open>a:focus,.navbar-default .navbar-nav>.open>a:hover{color:#555;background-color:#e7e7e7}@media (max-width:767px){.navbar-default .navbar-nav .open .dropdown-menu>li>a{color:#777}.navbar-default .navbar-nav .open .dropdown-menu>li>a:focus,.navbar-default .navbar-nav .open .dropdown-menu>li>a:hover{color:#333;background-color:transparent}.navbar-default .navbar-nav .open .dropdown-menu>.active>a,.navbar-default .navbar-nav .open .dropdown-menu>.active>a:focus,.navbar-default .navbar-nav .open .dropdown-menu>.active>a:hover{color:#555;background-color:#e7e7e7}.navbar-default .navbar-nav .open .dropdown-menu>.disabled>a,.navbar-default .navbar-nav .open .dropdown-menu>.disabled>a:focus,.navbar-default .navbar-nav .open .dropdown-menu>.disabled>a:hover{color:#ccc;background-color:transparent}}.navbar-default .navbar-link{color:#777}.navbar-default .navbar-link:hover{color:#333}.navbar-default .btn-link{color:#777}.navbar-default .btn-link:focus,.navbar-default .btn-link:hover{color:#333}.navbar-default .btn-link[disabled]:focus,.navbar-default .btn-link[disabled]:hover,fieldset[disabled] .navbar-default .btn-link:focus,fieldset[disabled] .navbar-default .btn-link:hover{color:#ccc}.navbar-inverse{background-color:#222;border-color:#080808}.navbar-inverse .navbar-brand{color:#9d9d9d}.navbar-inverse .navbar-brand:focus,.navbar-inverse .navbar-brand:hover{color:#fff;background-color:transparent}.navbar-inverse .navbar-text{color:#9d9d9d}.navbar-inverse .navbar-nav>li>a{color:#9d9d9d}.navbar-inverse .navbar-nav>li>a:focus,.navbar-inverse .navbar-nav>li>a:hover{color:#fff;background-color:transparent}.navbar-inverse .navbar-nav>.active>a,.navbar-inverse .navbar-nav>.active>a:focus,.navbar-inverse .navbar-nav>.active>a:hover{color:#fff;background-color:#080808}.navbar-inverse .navbar-nav>.disabled>a,.navbar-inverse .navbar-nav>.disabled>a:focus,.navbar-inverse .navbar-nav>.disabled>a:hover{color:#444;background-color:transparent}.navbar-inverse .navbar-toggle{border-color:#333}.navbar-inverse .navbar-toggle:focus,.navbar-inverse .navbar-toggle:hover{background-color:#333}.navbar-inverse .navbar-toggle .icon-bar{background-color:#fff}.navbar-inverse .navbar-collapse,.navbar-inverse .navbar-form{border-color:#101010}.navbar-inverse .navbar-nav>.open>a,.navbar-inverse .navbar-nav>.open>a:focus,.navbar-inverse .navbar-nav>.open>a:hover{color:#fff;background-color:#080808}@media (max-width:767px){.navbar-inverse .navbar-nav .open .dropdown-menu>.dropdown-header{border-color:#080808}.navbar-inverse .navbar-nav .open .dropdown-menu .divider{background-color:#080808}.navbar-inverse .navbar-nav .open .dropdown-menu>li>a{color:#9d9d9d}.navbar-inverse .navbar-nav .open .dropdown-menu>li>a:focus,.navbar-inverse .navbar-nav .open .dropdown-menu>li>a:hover{color:#fff;background-color:transparent}.navbar-inverse .navbar-nav .open .dropdown-menu>.active>a,.navbar-inverse .navbar-nav .open .dropdown-menu>.active>a:focus,.navbar-inverse .navbar-nav .open .dropdown-menu>.active>a:hover{color:#fff;background-color:#080808}.navbar-inverse .navbar-nav .open .dropdown-menu>.disabled>a,.navbar-inverse .navbar-nav .open .dropdown-menu>.disabled>a:focus,.navbar-inverse .navbar-nav .open .dropdown-menu>.disabled>a:hover{color:#444;background-color:transparent}}.navbar-inverse .navbar-link{color:#9d9d9d}.navbar-inverse .navbar-link:hover{color:#fff}.navbar-inverse .btn-link{color:#9d9d9d}.navbar-inverse .btn-link:focus,.navbar-inverse .btn-link:hover{color:#fff}.navbar-inverse .btn-link[disabled]:focus,.navbar-inverse .btn-link[disabled]:hover,fieldset[disabled] .navbar-inverse .btn-link:focus,fieldset[disabled] .navbar-inverse .btn-link:hover{color:#444}.breadcrumb{padding:8px 15px;margin-bottom:20px;list-style:none;background-color:#f5f5f5;border-radius:4px}.breadcrumb>li{display:inline-block}.breadcrumb>li+li:before{padding:0 5px;color:#ccc;content:"/\00a0"}.breadcrumb>.active{color:#777}.pagination{display:inline-block;padding-left:0;margin:20px 0;border-radius:4px}.pagination>li{display:inline}.pagination>li>a,.pagination>li>span{position:relative;float:left;padding:6px 12px;margin-left:-1px;line-height:1.42857143;color:#337ab7;text-decoration:none;background-color:#fff;border:1px solid #ddd}.pagination>li:first-child>a,.pagination>li:first-child>span{margin-left:0;border-top-left-radius:4px;border-bottom-left-radius:4px}.pagination>li:last-child>a,.pagination>li:last-child>span{border-top-right-radius:4px;border-bottom-right-radius:4px}.pagination>li>a:focus,.pagination>li>a:hover,.pagination>li>span:focus,.pagination>li>span:hover{z-index:2;color:#23527c;background-color:#eee;border-color:#ddd}.pagination>.active>a,.pagination>.active>a:focus,.pagination>.active>a:hover,.pagination>.active>span,.pagination>.active>span:focus,.pagination>.active>span:hover{z-index:3;color:#fff;cursor:default;background-color:#337ab7;border-color:#337ab7}.pagination>.disabled>a,.pagination>.disabled>a:focus,.pagination>.disabled>a:hover,.pagination>.disabled>span,.pagination>.disabled>span:focus,.pagination>.disabled>span:hover{color:#777;cursor:not-allowed;background-color:#fff;border-color:#ddd}.pagination-lg>li>a,.pagination-lg>li>span{padding:10px 16px;font-size:18px;line-height:1.3333333}.pagination-lg>li:first-child>a,.pagination-lg>li:first-child>span{border-top-left-radius:6px;border-bottom-left-radius:6px}.pagination-lg>li:last-child>a,.pagination-lg>li:last-child>span{border-top-right-radius:6px;border-bottom-right-radius:6px}.pagination-sm>li>a,.pagination-sm>li>span{padding:5px 10px;font-size:12px;line-height:1.5}.pagination-sm>li:first-child>a,.pagination-sm>li:first-child>span{border-top-left-radius:3px;border-bottom-left-radius:3px}.pagination-sm>li:last-child>a,.pagination-sm>li:last-child>span{border-top-right-radius:3px;border-bottom-right-radius:3px}.pager{padding-left:0;margin:20px 0;text-align:center;list-style:none}.pager li{display:inline}.pager li>a,.pager li>span{display:inline-block;padding:5px 14px;background-color:#fff;border:1px solid #ddd;border-radius:15px}.pager li>a:focus,.pager li>a:hover{text-decoration:none;background-color:#eee}.pager .next>a,.pager .next>span{float:right}.pager .previous>a,.pager .previous>span{float:left}.pager .disabled>a,.pager .disabled>a:focus,.pager .disabled>a:hover,.pager .disabled>span{color:#777;cursor:not-allowed;background-color:#fff}.label{display:inline;padding:.2em .6em .3em;font-size:75%;font-weight:700;line-height:1;color:#fff;text-align:center;white-space:nowrap;vertical-align:baseline;border-radius:.25em}a.label:focus,a.label:hover{color:#fff;text-decoration:none;cursor:pointer}.label:empty{display:none}.btn .label{position:relative;top:-1px}.label-default{background-color:#777}.label-default[href]:focus,.label-default[href]:hover{background-color:#5e5e5e}.label-primary{background-color:#337ab7}.label-primary[href]:focus,.label-primary[href]:hover{background-color:#286090}.label-success{background-color:#5cb85c}.label-success[href]:focus,.label-success[href]:hover{background-color:#449d44}.label-info{background-color:#5bc0de}.label-info[href]:focus,.label-info[href]:hover{background-color:#31b0d5}.label-warning{background-color:#f0ad4e}.label-warning[href]:focus,.label-warning[href]:hover{background-color:#ec971f}.label-danger{background-color:#d9534f}.label-danger[href]:focus,.label-danger[href]:hover{background-color:#c9302c}.badge{display:inline-block;min-width:10px;padding:3px 7px;font-size:12px;font-weight:700;line-height:1;color:#fff;text-align:center;white-space:nowrap;vertical-align:middle;background-color:#777;border-radius:10px}.badge:empty{display:none}.btn .badge{position:relative;top:-1px}.btn-group-xs>.btn .badge,.btn-xs .badge{top:0;padding:1px 5px}a.badge:focus,a.badge:hover{color:#fff;text-decoration:none;cursor:pointer}.list-group-item.active>.badge,.nav-pills>.active>a>.badge{color:#337ab7;background-color:#fff}.list-group-item>.badge{float:right}.list-group-item>.badge+.badge{margin-right:5px}.nav-pills>li>a>.badge{margin-left:3px}.jumbotron{padding-top:30px;padding-bottom:30px;margin-bottom:30px;color:inherit;background-color:#eee}.jumbotron .h1,.jumbotron h1{color:inherit}.jumbotron p{margin-bottom:15px;font-size:21px;font-weight:200}.jumbotron>hr{border-top-color:#d5d5d5}.container .jumbotron,.container-fluid .jumbotron{padding-right:15px;padding-left:15px;border-radius:6px}.jumbotron .container{max-width:100%}@media screen and (min-width:768px){.jumbotron{padding-top:48px;padding-bottom:48px}.container .jumbotron,.container-fluid .jumbotron{padding-right:60px;padding-left:60px}.jumbotron .h1,.jumbotron h1{font-size:63px}}.thumbnail{display:block;padding:4px;margin-bottom:20px;line-height:1.42857143;background-color:#fff;border:1px solid #ddd;border-radius:4px;-webkit-transition:border .2s ease-in-out;-o-transition:border .2s ease-in-out;transition:border .2s ease-in-out}.thumbnail a>img,.thumbnail>img{margin-right:auto;margin-left:auto}a.thumbnail.active,a.thumbnail:focus,a.thumbnail:hover{border-color:#337ab7}.thumbnail .caption{padding:9px;color:#333}.alert{padding:15px;margin-bottom:20px;border:1px solid transparent;border-radius:4px}.alert h4{margin-top:0;color:inherit}.alert .alert-link{font-weight:700}.alert>p,.alert>ul{margin-bottom:0}.alert>p+p{margin-top:5px}.alert-dismissable,.alert-dismissible{padding-right:35px}.alert-dismissable .close,.alert-dismissible .close{position:relative;top:-2px;right:-21px;color:inherit}.alert-success{color:#3c763d;background-color:#dff0d8;border-color:#d6e9c6}.alert-success hr{border-top-color:#c9e2b3}.alert-success .alert-link{color:#2b542c}.alert-info{color:#31708f;background-color:#d9edf7;border-color:#bce8f1}.alert-info hr{border-top-color:#a6e1ec}.alert-info .alert-link{color:#245269}.alert-warning{color:#8a6d3b;background-color:#fcf8e3;border-color:#faebcc}.alert-warning hr{border-top-color:#f7e1b5}.alert-warning .alert-link{color:#66512c}.alert-danger{color:#a94442;background-color:#f2dede;border-color:#ebccd1}.alert-danger hr{border-top-color:#e4b9c0}.alert-danger .alert-link{color:#843534}@-webkit-keyframes progress-bar-stripes{from{background-position:40px 0}to{background-position:0 0}}@-o-keyframes progress-bar-stripes{from{background-position:40px 0}to{background-position:0 0}}@keyframes progress-bar-stripes{from{background-position:40px 0}to{background-position:0 0}}.progress{height:20px;margin-bottom:20px;overflow:hidden;background-color:#f5f5f5;border-radius:4px;-webkit-box-shadow:inset 0 1px 2px rgba(0,0,0,.1);box-shadow:inset 0 1px 2px rgba(0,0,0,.1)}.progress-bar{float:left;width:0;height:100%;font-size:12px;line-height:20px;color:#fff;text-align:center;background-color:#337ab7;-webkit-box-shadow:inset 0 -1px 0 rgba(0,0,0,.15);box-shadow:inset 0 -1px 0 rgba(0,0,0,.15);-webkit-transition:width .6s ease;-o-transition:width .6s ease;transition:width .6s ease}.progress-bar-striped,.progress-striped .progress-bar{background-image:-webkit-linear-gradient(45deg,rgba(255,255,255,.15) 25%,transparent 25%,transparent 50%,rgba(255,255,255,.15) 50%,rgba(255,255,255,.15) 75%,transparent 75%,transparent);background-image:-o-linear-gradient(45deg,rgba(255,255,255,.15) 25%,transparent 25%,transparent 50%,rgba(255,255,255,.15) 50%,rgba(255,255,255,.15) 75%,transparent 75%,transparent);background-image:linear-gradient(45deg,rgba(255,255,255,.15) 25%,transparent 25%,transparent 50%,rgba(255,255,255,.15) 50%,rgba(255,255,255,.15) 75%,transparent 75%,transparent);-webkit-background-size:40px 40px;background-size:40px 40px}.progress-bar.active,.progress.active .progress-bar{-webkit-animation:progress-bar-stripes 2s linear infinite;-o-animation:progress-bar-stripes 2s linear infinite;animation:progress-bar-stripes 2s linear infinite}.progress-bar-success{background-color:#5cb85c}.progress-striped .progress-bar-success{background-image:-webkit-linear-gradient(45deg,rgba(255,255,255,.15) 25%,transparent 25%,transparent 50%,rgba(255,255,255,.15) 50%,rgba(255,255,255,.15) 75%,transparent 75%,transparent);background-image:-o-linear-gradient(45deg,rgba(255,255,255,.15) 25%,transparent 25%,transparent 50%,rgba(255,255,255,.15) 50%,rgba(255,255,255,.15) 75%,transparent 75%,transparent);background-image:linear-gradient(45deg,rgba(255,255,255,.15) 25%,transparent 25%,transparent 50%,rgba(255,255,255,.15) 50%,rgba(255,255,255,.15) 75%,transparent 75%,transparent)}.progress-bar-info{background-color:#5bc0de}.progress-striped .progress-bar-info{background-image:-webkit-linear-gradient(45deg,rgba(255,255,255,.15) 25%,transparent 25%,transparent 50%,rgba(255,255,255,.15) 50%,rgba(255,255,255,.15) 75%,transparent 75%,transparent);background-image:-o-linear-gradient(45deg,rgba(255,255,255,.15) 25%,transparent 25%,transparent 50%,rgba(255,255,255,.15) 50%,rgba(255,255,255,.15) 75%,transparent 75%,transparent);background-image:linear-gradient(45deg,rgba(255,255,255,.15) 25%,transparent 25%,transparent 50%,rgba(255,255,255,.15) 50%,rgba(255,255,255,.15) 75%,transparent 75%,transparent)}.progress-bar-warning{background-color:#f0ad4e}.progress-striped .progress-bar-warning{background-image:-webkit-linear-gradient(45deg,rgba(255,255,255,.15) 25%,transparent 25%,transparent 50%,rgba(255,255,255,.15) 50%,rgba(255,255,255,.15) 75%,transparent 75%,transparent);background-image:-o-linear-gradient(45deg,rgba(255,255,255,.15) 25%,transparent 25%,transparent 50%,rgba(255,255,255,.15) 50%,rgba(255,255,255,.15) 75%,transparent 75%,transparent);background-image:linear-gradient(45deg,rgba(255,255,255,.15) 25%,transparent 25%,transparent 50%,rgba(255,255,255,.15) 50%,rgba(255,255,255,.15) 75%,transparent 75%,transparent)}.progress-bar-danger{background-color:#d9534f}.progress-striped .progress-bar-danger{background-image:-webkit-linear-gradient(45deg,rgba(255,255,255,.15) 25%,transparent 25%,transparent 50%,rgba(255,255,255,.15) 50%,rgba(255,255,255,.15) 75%,transparent 75%,transparent);background-image:-o-linear-gradient(45deg,rgba(255,255,255,.15) 25%,transparent 25%,transparent 50%,rgba(255,255,255,.15) 50%,rgba(255,255,255,.15) 75%,transparent 75%,transparent);background-image:linear-gradient(45deg,rgba(255,255,255,.15) 25%,transparent 25%,transparent 50%,rgba(255,255,255,.15) 50%,rgba(255,255,255,.15) 75%,transparent 75%,transparent)}.media{margin-top:15px}.media:first-child{margin-top:0}.media,.media-body{overflow:hidden;zoom:1}.media-body{width:10000px}.media-object{display:block}.media-object.img-thumbnail{max-width:none}.media-right,.media>.pull-right{padding-left:10px}.media-left,.media>.pull-left{padding-right:10px}.media-body,.media-left,.media-right{display:table-cell;vertical-align:top}.media-middle{vertical-align:middle}.media-bottom{vertical-align:bottom}.media-heading{margin-top:0;margin-bottom:5px}.media-list{padding-left:0;list-style:none}.list-group{padding-left:0;margin-bottom:20px}.list-group-item{position:relative;display:block;padding:10px 15px;margin-bottom:-1px;background-color:#fff;border:1px solid #ddd}.list-group-item:first-child{border-top-left-radius:4px;border-top-right-radius:4px}.list-group-item:last-child{margin-bottom:0;border-bottom-right-radius:4px;border-bottom-left-radius:4px}a.list-group-item,button.list-group-item{color:#555}a.list-group-item .list-group-item-heading,button.list-group-item .list-group-item-heading{color:#333}a.list-group-item:focus,a.list-group-item:hover,button.list-group-item:focus,button.list-group-item:hover{color:#555;text-decoration:none;background-color:#f5f5f5}button.list-group-item{width:100%;text-align:left}.list-group-item.disabled,.list-group-item.disabled:focus,.list-group-item.disabled:hover{color:#777;cursor:not-allowed;background-color:#eee}.list-group-item.disabled .list-group-item-heading,.list-group-item.disabled:focus .list-group-item-heading,.list-group-item.disabled:hover .list-group-item-heading{color:inherit}.list-group-item.disabled .list-group-item-text,.list-group-item.disabled:focus .list-group-item-text,.list-group-item.disabled:hover .list-group-item-text{color:#777}.list-group-item.active,.list-group-item.active:focus,.list-group-item.active:hover{z-index:2;color:#fff;background-color:#337ab7;border-color:#337ab7}.list-group-item.active .list-group-item-heading,.list-group-item.active .list-group-item-heading>.small,.list-group-item.active .list-group-item-heading>small,.list-group-item.active:focus .list-group-item-heading,.list-group-item.active:focus .list-group-item-heading>.small,.list-group-item.active:focus .list-group-item-heading>small,.list-group-item.active:hover .list-group-item-heading,.list-group-item.active:hover .list-group-item-heading>.small,.list-group-item.active:hover .list-group-item-heading>small{color:inherit}.list-group-item.active .list-group-item-text,.list-group-item.active:focus .list-group-item-text,.list-group-item.active:hover .list-group-item-text{color:#c7ddef}.list-group-item-success{color:#3c763d;background-color:#dff0d8}a.list-group-item-success,button.list-group-item-success{color:#3c763d}a.list-group-item-success .list-group-item-heading,button.list-group-item-success .list-group-item-heading{color:inherit}a.list-group-item-success:focus,a.list-group-item-success:hover,button.list-group-item-success:focus,button.list-group-item-success:hover{color:#3c763d;background-color:#d0e9c6}a.list-group-item-success.active,a.list-group-item-success.active:focus,a.list-group-item-success.active:hover,button.list-group-item-success.active,button.list-group-item-success.active:focus,button.list-group-item-success.active:hover{color:#fff;background-color:#3c763d;border-color:#3c763d}.list-group-item-info{color:#31708f;background-color:#d9edf7}a.list-group-item-info,button.list-group-item-info{color:#31708f}a.list-group-item-info .list-group-item-heading,button.list-group-item-info .list-group-item-heading{color:inherit}a.list-group-item-info:focus,a.list-group-item-info:hover,button.list-group-item-info:focus,button.list-group-item-info:hover{color:#31708f;background-color:#c4e3f3}a.list-group-item-info.active,a.list-group-item-info.active:focus,a.list-group-item-info.active:hover,button.list-group-item-info.active,button.list-group-item-info.active:focus,button.list-group-item-info.active:hover{color:#fff;background-color:#31708f;border-color:#31708f}.list-group-item-warning{color:#8a6d3b;background-color:#fcf8e3}a.list-group-item-warning,button.list-group-item-warning{color:#8a6d3b}a.list-group-item-warning .list-group-item-heading,button.list-group-item-warning .list-group-item-heading{color:inherit}a.list-group-item-warning:focus,a.list-group-item-warning:hover,button.list-group-item-warning:focus,button.list-group-item-warning:hover{color:#8a6d3b;background-color:#faf2cc}a.list-group-item-warning.active,a.list-group-item-warning.active:focus,a.list-group-item-warning.active:hover,button.list-group-item-warning.active,button.list-group-item-warning.active:focus,button.list-group-item-warning.active:hover{color:#fff;background-color:#8a6d3b;border-color:#8a6d3b}.list-group-item-danger{color:#a94442;background-color:#f2dede}a.list-group-item-danger,button.list-group-item-danger{color:#a94442}a.list-group-item-danger .list-group-item-heading,button.list-group-item-danger .list-group-item-heading{color:inherit}a.list-group-item-danger:focus,a.list-group-item-danger:hover,button.list-group-item-danger:focus,button.list-group-item-danger:hover{color:#a94442;background-color:#ebcccc}a.list-group-item-danger.active,a.list-group-item-danger.active:focus,a.list-group-item-danger.active:hover,button.list-group-item-danger.active,button.list-group-item-danger.active:focus,button.list-group-item-danger.active:hover{color:#fff;background-color:#a94442;border-color:#a94442}.list-group-item-heading{margin-top:0;margin-bottom:5px}.list-group-item-text{margin-bottom:0;line-height:1.3}.panel{margin-bottom:20px;background-color:#fff;border:1px solid transparent;border-radius:4px;-webkit-box-shadow:0 1px 1px rgba(0,0,0,.05);box-shadow:0 1px 1px rgba(0,0,0,.05)}.panel-body{padding:15px}.panel-heading{padding:10px 15px;border-bottom:1px solid transparent;border-top-left-radius:3px;border-top-right-radius:3px}.panel-heading>.dropdown .dropdown-toggle{color:inherit}.panel-title{margin-top:0;margin-bottom:0;font-size:16px;color:inherit}.panel-title>.small,.panel-title>.small>a,.panel-title>a,.panel-title>small,.panel-title>small>a{color:inherit}.panel-footer{padding:10px 15px;background-color:#f5f5f5;border-top:1px solid #ddd;border-bottom-right-radius:3px;border-bottom-left-radius:3px}.panel>.list-group,.panel>.panel-collapse>.list-group{margin-bottom:0}.panel>.list-group .list-group-item,.panel>.panel-collapse>.list-group .list-group-item{border-width:1px 0;border-radius:0}.panel>.list-group:first-child .list-group-item:first-child,.panel>.panel-collapse>.list-group:first-child .list-group-item:first-child{border-top:0;border-top-left-radius:3px;border-top-right-radius:3px}.panel>.list-group:last-child .list-group-item:last-child,.panel>.panel-collapse>.list-group:last-child .list-group-item:last-child{border-bottom:0;border-bottom-right-radius:3px;border-bottom-left-radius:3px}.panel>.panel-heading+.panel-collapse>.list-group .list-group-item:first-child{border-top-left-radius:0;border-top-right-radius:0}.panel-heading+.list-group .list-group-item:first-child{border-top-width:0}.list-group+.panel-footer{border-top-width:0}.panel>.panel-collapse>.table,.panel>.table,.panel>.table-responsive>.table{margin-bottom:0}.panel>.panel-collapse>.table caption,.panel>.table caption,.panel>.table-responsive>.table caption{padding-right:15px;padding-left:15px}.panel>.table-responsive:first-child>.table:first-child,.panel>.table:first-child{border-top-left-radius:3px;border-top-right-radius:3px}.panel>.table-responsive:first-child>.table:first-child>tbody:first-child>tr:first-child,.panel>.table-responsive:first-child>.table:first-child>thead:first-child>tr:first-child,.panel>.table:first-child>tbody:first-child>tr:first-child,.panel>.table:first-child>thead:first-child>tr:first-child{border-top-left-radius:3px;border-top-right-radius:3px}.panel>.table-responsive:first-child>.table:first-child>tbody:first-child>tr:first-child td:first-child,.panel>.table-responsive:first-child>.table:first-child>tbody:first-child>tr:first-child th:first-child,.panel>.table-responsive:first-child>.table:first-child>thead:first-child>tr:first-child td:first-child,.panel>.table-responsive:first-child>.table:first-child>thead:first-child>tr:first-child th:first-child,.panel>.table:first-child>tbody:first-child>tr:first-child td:first-child,.panel>.table:first-child>tbody:first-child>tr:first-child th:first-child,.panel>.table:first-child>thead:first-child>tr:first-child td:first-child,.panel>.table:first-child>thead:first-child>tr:first-child th:first-child{border-top-left-radius:3px}.panel>.table-responsive:first-child>.table:first-child>tbody:first-child>tr:first-child td:last-child,.panel>.table-responsive:first-child>.table:first-child>tbody:first-child>tr:first-child th:last-child,.panel>.table-responsive:first-child>.table:first-child>thead:first-child>tr:first-child td:last-child,.panel>.table-responsive:first-child>.table:first-child>thead:first-child>tr:first-child th:last-child,.panel>.table:first-child>tbody:first-child>tr:first-child td:last-child,.panel>.table:first-child>tbody:first-child>tr:first-child th:last-child,.panel>.table:first-child>thead:first-child>tr:first-child td:last-child,.panel>.table:first-child>thead:first-child>tr:first-child th:last-child{border-top-right-radius:3px}.panel>.table-responsive:last-child>.table:last-child,.panel>.table:last-child{border-bottom-right-radius:3px;border-bottom-left-radius:3px}.panel>.table-responsive:last-child>.table:last-child>tbody:last-child>tr:last-child,.panel>.table-responsive:last-child>.table:last-child>tfoot:last-child>tr:last-child,.panel>.table:last-child>tbody:last-child>tr:last-child,.panel>.table:last-child>tfoot:last-child>tr:last-child{border-bottom-right-radius:3px;border-bottom-left-radius:3px}.panel>.table-responsive:last-child>.table:last-child>tbody:last-child>tr:last-child td:first-child,.panel>.table-responsive:last-child>.table:last-child>tbody:last-child>tr:last-child th:first-child,.panel>.table-responsive:last-child>.table:last-child>tfoot:last-child>tr:last-child td:first-child,.panel>.table-responsive:last-child>.table:last-child>tfoot:last-child>tr:last-child th:first-child,.panel>.table:last-child>tbody:last-child>tr:last-child td:first-child,.panel>.table:last-child>tbody:last-child>tr:last-child th:first-child,.panel>.table:last-child>tfoot:last-child>tr:last-child td:first-child,.panel>.table:last-child>tfoot:last-child>tr:last-child th:first-child{border-bottom-left-radius:3px}.panel>.table-responsive:last-child>.table:last-child>tbody:last-child>tr:last-child td:last-child,.panel>.table-responsive:last-child>.table:last-child>tbody:last-child>tr:last-child th:last-child,.panel>.table-responsive:last-child>.table:last-child>tfoot:last-child>tr:last-child td:last-child,.panel>.table-responsive:last-child>.table:last-child>tfoot:last-child>tr:last-child th:last-child,.panel>.table:last-child>tbody:last-child>tr:last-child td:last-child,.panel>.table:last-child>tbody:last-child>tr:last-child th:last-child,.panel>.table:last-child>tfoot:last-child>tr:last-child td:last-child,.panel>.table:last-child>tfoot:last-child>tr:last-child th:last-child{border-bottom-right-radius:3px}.panel>.panel-body+.table,.panel>.panel-body+.table-responsive,.panel>.table+.panel-body,.panel>.table-responsive+.panel-body{border-top:1px solid #ddd}.panel>.table>tbody:first-child>tr:first-child td,.panel>.table>tbody:first-child>tr:first-child th{border-top:0}.panel>.table-bordered,.panel>.table-responsive>.table-bordered{border:0}.panel>.table-bordered>tbody>tr>td:first-child,.panel>.table-bordered>tbody>tr>th:first-child,.panel>.table-bordered>tfoot>tr>td:first-child,.panel>.table-bordered>tfoot>tr>th:first-child,.panel>.table-bordered>thead>tr>td:first-child,.panel>.table-bordered>thead>tr>th:first-child,.panel>.table-responsive>.table-bordered>tbody>tr>td:first-child,.panel>.table-responsive>.table-bordered>tbody>tr>th:first-child,.panel>.table-responsive>.table-bordered>tfoot>tr>td:first-child,.panel>.table-responsive>.table-bordered>tfoot>tr>th:first-child,.panel>.table-responsive>.table-bordered>thead>tr>td:first-child,.panel>.table-responsive>.table-bordered>thead>tr>th:first-child{border-left:0}.panel>.table-bordered>tbody>tr>td:last-child,.panel>.table-bordered>tbody>tr>th:last-child,.panel>.table-bordered>tfoot>tr>td:last-child,.panel>.table-bordered>tfoot>tr>th:last-child,.panel>.table-bordered>thead>tr>td:last-child,.panel>.table-bordered>thead>tr>th:last-child,.panel>.table-responsive>.table-bordered>tbody>tr>td:last-child,.panel>.table-responsive>.table-bordered>tbody>tr>th:last-child,.panel>.table-responsive>.table-bordered>tfoot>tr>td:last-child,.panel>.table-responsive>.table-bordered>tfoot>tr>th:last-child,.panel>.table-responsive>.table-bordered>thead>tr>td:last-child,.panel>.table-responsive>.table-bordered>thead>tr>th:last-child{border-right:0}.panel>.table-bordered>tbody>tr:first-child>td,.panel>.table-bordered>tbody>tr:first-child>th,.panel>.table-bordered>thead>tr:first-child>td,.panel>.table-bordered>thead>tr:first-child>th,.panel>.table-responsive>.table-bordered>tbody>tr:first-child>td,.panel>.table-responsive>.table-bordered>tbody>tr:first-child>th,.panel>.table-responsive>.table-bordered>thead>tr:first-child>td,.panel>.table-responsive>.table-bordered>thead>tr:first-child>th{border-bottom:0}.panel>.table-bordered>tbody>tr:last-child>td,.panel>.table-bordered>tbody>tr:last-child>th,.panel>.table-bordered>tfoot>tr:last-child>td,.panel>.table-bordered>tfoot>tr:last-child>th,.panel>.table-responsive>.table-bordered>tbody>tr:last-child>td,.panel>.table-responsive>.table-bordered>tbody>tr:last-child>th,.panel>.table-responsive>.table-bordered>tfoot>tr:last-child>td,.panel>.table-responsive>.table-bordered>tfoot>tr:last-child>th{border-bottom:0}.panel>.table-responsive{margin-bottom:0;border:0}.panel-group{margin-bottom:20px}.panel-group .panel{margin-bottom:0;border-radius:4px}.panel-group .panel+.panel{margin-top:5px}.panel-group .panel-heading{border-bottom:0}.panel-group .panel-heading+.panel-collapse>.list-group,.panel-group .panel-heading+.panel-collapse>.panel-body{border-top:1px solid #ddd}.panel-group .panel-footer{border-top:0}.panel-group .panel-footer+.panel-collapse .panel-body{border-bottom:1px solid #ddd}.panel-default{border-color:#ddd}.panel-default>.panel-heading{color:#333;background-color:#f5f5f5;border-color:#ddd}.panel-default>.panel-heading+.panel-collapse>.panel-body{border-top-color:#ddd}.panel-default>.panel-heading .badge{color:#f5f5f5;background-color:#333}.panel-default>.panel-footer+.panel-collapse>.panel-body{border-bottom-color:#ddd}.panel-primary{border-color:#337ab7}.panel-primary>.panel-heading{color:#fff;background-color:#337ab7;border-color:#337ab7}.panel-primary>.panel-heading+.panel-collapse>.panel-body{border-top-color:#337ab7}.panel-primary>.panel-heading .badge{color:#337ab7;background-color:#fff}.panel-primary>.panel-footer+.panel-collapse>.panel-body{border-bottom-color:#337ab7}.panel-success{border-color:#d6e9c6}.panel-success>.panel-heading{color:#3c763d;background-color:#dff0d8;border-color:#d6e9c6}.panel-success>.panel-heading+.panel-collapse>.panel-body{border-top-color:#d6e9c6}.panel-success>.panel-heading .badge{color:#dff0d8;background-color:#3c763d}.panel-success>.panel-footer+.panel-collapse>.panel-body{border-bottom-color:#d6e9c6}.panel-info{border-color:#bce8f1}.panel-info>.panel-heading{color:#31708f;background-color:#d9edf7;border-color:#bce8f1}.panel-info>.panel-heading+.panel-collapse>.panel-body{border-top-color:#bce8f1}.panel-info>.panel-heading .badge{color:#d9edf7;background-color:#31708f}.panel-info>.panel-footer+.panel-collapse>.panel-body{border-bottom-color:#bce8f1}.panel-warning{border-color:#faebcc}.panel-warning>.panel-heading{color:#8a6d3b;background-color:#fcf8e3;border-color:#faebcc}.panel-warning>.panel-heading+.panel-collapse>.panel-body{border-top-color:#faebcc}.panel-warning>.panel-heading .badge{color:#fcf8e3;background-color:#8a6d3b}.panel-warning>.panel-footer+.panel-collapse>.panel-body{border-bottom-color:#faebcc}.panel-danger{border-color:#ebccd1}.panel-danger>.panel-heading{color:#a94442;background-color:#f2dede;border-color:#ebccd1}.panel-danger>.panel-heading+.panel-collapse>.panel-body{border-top-color:#ebccd1}.panel-danger>.panel-heading .badge{color:#f2dede;background-color:#a94442}.panel-danger>.panel-footer+.panel-collapse>.panel-body{border-bottom-color:#ebccd1}.embed-responsive{position:relative;display:block;height:0;padding:0;overflow:hidden}.embed-responsive .embed-responsive-item,.embed-responsive embed,.embed-responsive iframe,.embed-responsive object,.embed-responsive video{position:absolute;top:0;bottom:0;left:0;width:100%;height:100%;border:0}.embed-responsive-16by9{padding-bottom:56.25%}.embed-responsive-4by3{padding-bottom:75%}.well{min-height:20px;padding:19px;margin-bottom:20px;background-color:#f5f5f5;border:1px solid #e3e3e3;border-radius:4px;-webkit-box-shadow:inset 0 1px 1px rgba(0,0,0,.05);box-shadow:inset 0 1px 1px rgba(0,0,0,.05)}.well blockquote{border-color:#ddd;border-color:rgba(0,0,0,.15)}.well-lg{padding:24px;border-radius:6px}.well-sm{padding:9px;border-radius:3px}.close{float:right;font-size:21px;font-weight:700;line-height:1;color:#000;text-shadow:0 1px 0 #fff;opacity:.2}.close:focus,.close:hover{color:#000;text-decoration:none;cursor:pointer;opacity:.5}button.close{-webkit-appearance:none;padding:0;cursor:pointer;background:0 0;border:0}.modal-open{overflow:hidden}.modal{position:fixed;top:0;right:0;bottom:0;left:0;z-index:1050;display:none;overflow:hidden;-webkit-overflow-scrolling:touch;outline:0}.modal.fade .modal-dialog{-webkit-transition:-webkit-transform .3s ease-out;-o-transition:-o-transform .3s ease-out;transition:transform .3s ease-out;-webkit-transform:translate(0,-25%);-ms-transform:translate(0,-25%);-o-transform:translate(0,-25%);transform:translate(0,-25%)}.modal.in .modal-dialog{-webkit-transform:translate(0,0);-ms-transform:translate(0,0);-o-transform:translate(0,0);transform:translate(0,0)}.modal-open .modal{overflow-x:hidden;overflow-y:auto}.modal-dialog{position:relative;width:auto;margin:10px}.modal-content{position:relative;background-color:#fff;-webkit-background-clip:padding-box;background-clip:padding-box;border:1px solid #999;border:1px solid rgba(0,0,0,.2);border-radius:6px;outline:0;-webkit-box-shadow:0 3px 9px rgba(0,0,0,.5);box-shadow:0 3px 9px rgba(0,0,0,.5)}.modal-backdrop{position:fixed;top:0;right:0;bottom:0;left:0;z-index:1040;background-color:#000}.modal-backdrop.fade{opacity:0}.modal-backdrop.in{opacity:.5}.modal-header{padding:15px;border-bottom:1px solid #e5e5e5}.modal-header .close{margin-top:-2px}.modal-title{margin:0;line-height:1.42857143}.modal-body{position:relative;padding:15px}.modal-footer{padding:15px;text-align:right;border-top:1px solid #e5e5e5}.modal-footer .btn+.btn{margin-bottom:0;margin-left:5px}.modal-footer .btn-group .btn+.btn{margin-left:-1px}.modal-footer .btn-block+.btn-block{margin-left:0}.modal-scrollbar-measure{position:absolute;top:-9999px;width:50px;height:50px;overflow:scroll}@media (min-width:768px){.modal-dialog{width:600px;margin:30px auto}.modal-content{-webkit-box-shadow:0 5px 15px rgba(0,0,0,.5);box-shadow:0 5px 15px rgba(0,0,0,.5)}.modal-sm{width:300px}}@media (min-width:992px){.modal-lg{width:900px}}.tooltip{position:absolute;z-index:1070;display:block;font-family:"Helvetica Neue",Helvetica,Arial,sans-serif;font-size:12px;font-style:normal;font-weight:400;line-height:1.42857143;text-align:left;text-align:start;text-decoration:none;text-shadow:none;text-transform:none;letter-spacing:normal;word-break:normal;word-spacing:normal;word-wrap:normal;white-space:normal;opacity:0;line-break:auto}.tooltip.in{opacity:.9}.tooltip.top{padding:5px 0;margin-top:-3px}.tooltip.right{padding:0 5px;margin-left:3px}.tooltip.bottom{padding:5px 0;margin-top:3px}.tooltip.left{padding:0 5px;margin-left:-3px}.tooltip-inner{max-width:200px;padding:3px 8px;color:#fff;text-align:center;background-color:#000;border-radius:4px}.tooltip-arrow{position:absolute;width:0;height:0;border-color:transparent;border-style:solid}.tooltip.top .tooltip-arrow{bottom:0;left:50%;margin-left:-5px;border-width:5px 5px 0;border-top-color:#000}.tooltip.top-left .tooltip-arrow{right:5px;bottom:0;margin-bottom:-5px;border-width:5px 5px 0;border-top-color:#000}.tooltip.top-right .tooltip-arrow{bottom:0;left:5px;margin-bottom:-5px;border-width:5px 5px 0;border-top-color:#000}.tooltip.right .tooltip-arrow{top:50%;left:0;margin-top:-5px;border-width:5px 5px 5px 0;border-right-color:#000}.tooltip.left .tooltip-arrow{top:50%;right:0;margin-top:-5px;border-width:5px 0 5px 5px;border-left-color:#000}.tooltip.bottom .tooltip-arrow{top:0;left:50%;margin-left:-5px;border-width:0 5px 5px;border-bottom-color:#000}.tooltip.bottom-left .tooltip-arrow{top:0;right:5px;margin-top:-5px;border-width:0 5px 5px;border-bottom-color:#000}.tooltip.bottom-right .tooltip-arrow{top:0;left:5px;margin-top:-5px;border-width:0 5px 5px;border-bottom-color:#000}.popover{position:absolute;top:0;left:0;z-index:1060;display:none;max-width:276px;padding:1px;font-family:"Helvetica Neue",Helvetica,Arial,sans-serif;font-size:14px;font-style:normal;font-weight:400;line-height:1.42857143;text-align:left;text-align:start;text-decoration:none;text-shadow:none;text-transform:none;letter-spacing:normal;word-break:normal;word-spacing:normal;word-wrap:normal;white-space:normal;background-color:#fff;-webkit-background-clip:padding-box;background-clip:padding-box;border:1px solid #ccc;border:1px solid rgba(0,0,0,.2);border-radius:6px;-webkit-box-shadow:0 5px 10px rgba(0,0,0,.2);box-shadow:0 5px 10px rgba(0,0,0,.2);line-break:auto}.popover.top{margin-top:-10px}.popover.right{margin-left:10px}.popover.bottom{margin-top:10px}.popover.left{margin-left:-10px}.popover-title{padding:8px 14px;margin:0;font-size:14px;background-color:#f7f7f7;border-bottom:1px solid #ebebeb;border-radius:5px 5px 0 0}.popover-content{padding:9px 14px}.popover>.arrow,.popover>.arrow:after{position:absolute;display:block;width:0;height:0;border-color:transparent;border-style:solid}.popover>.arrow{border-width:11px}.popover>.arrow:after{content:"";border-width:10px}.popover.top>.arrow{bottom:-11px;left:50%;margin-left:-11px;border-top-color:#999;border-top-color:rgba(0,0,0,.25);border-bottom-width:0}.popover.top>.arrow:after{bottom:1px;margin-left:-10px;content:" ";border-top-color:#fff;border-bottom-width:0}.popover.right>.arrow{top:50%;left:-11px;margin-top:-11px;border-right-color:#999;border-right-color:rgba(0,0,0,.25);border-left-width:0}.popover.right>.arrow:after{bottom:-10px;left:1px;content:" ";border-right-color:#fff;border-left-width:0}.popover.bottom>.arrow{top:-11px;left:50%;margin-left:-11px;border-top-width:0;border-bottom-color:#999;border-bottom-color:rgba(0,0,0,.25)}.popover.bottom>.arrow:after{top:1px;margin-left:-10px;content:" ";border-top-width:0;border-bottom-color:#fff}.popover.left>.arrow{top:50%;right:-11px;margin-top:-11px;border-right-width:0;border-left-color:#999;border-left-color:rgba(0,0,0,.25)}.popover.left>.arrow:after{right:1px;bottom:-10px;content:" ";border-right-width:0;border-left-color:#fff}.carousel{position:relative}.carousel-inner{position:relative;width:100%;overflow:hidden}.carousel-inner>.item{position:relative;display:none;-webkit-transition:.6s ease-in-out left;-o-transition:.6s ease-in-out left;transition:.6s ease-in-out left}.carousel-inner>.item>a>img,.carousel-inner>.item>img{line-height:1}@media all and (transform-3d),(-webkit-transform-3d){.carousel-inner>.item{-webkit-transition:-webkit-transform .6s ease-in-out;-o-transition:-o-transform .6s ease-in-out;transition:transform .6s ease-in-out;-webkit-backface-visibility:hidden;backface-visibility:hidden;-webkit-perspective:1000px;perspective:1000px}.carousel-inner>.item.active.right,.carousel-inner>.item.next{left:0;-webkit-transform:translate3d(100%,0,0);transform:translate3d(100%,0,0)}.carousel-inner>.item.active.left,.carousel-inner>.item.prev{left:0;-webkit-transform:translate3d(-100%,0,0);transform:translate3d(-100%,0,0)}.carousel-inner>.item.active,.carousel-inner>.item.next.left,.carousel-inner>.item.prev.right{left:0;-webkit-transform:translate3d(0,0,0);transform:translate3d(0,0,0)}}.carousel-inner>.active,.carousel-inner>.next,.carousel-inner>.prev{display:block}.carousel-inner>.active{left:0}.carousel-inner>.next,.carousel-inner>.prev{position:absolute;top:0;width:100%}.carousel-inner>.next{left:100%}.carousel-inner>.prev{left:-100%}.carousel-inner>.next.left,.carousel-inner>.prev.right{left:0}.carousel-inner>.active.left{left:-100%}.carousel-inner>.active.right{left:100%}.carousel-control{position:absolute;top:0;bottom:0;left:0;width:15%;font-size:20px;color:#fff;text-align:center;text-shadow:0 1px 2px rgba(0,0,0,.6);background-color:rgba(0,0,0,0);opacity:.5}.carousel-control.left{background-image:-webkit-linear-gradient(left,rgba(0,0,0,.5) 0,rgba(0,0,0,.0001) 100%);background-image:-o-linear-gradient(left,rgba(0,0,0,.5) 0,rgba(0,0,0,.0001) 100%);background-image:-webkit-gradient(linear,left top,right top,from(rgba(0,0,0,.5)),to(rgba(0,0,0,.0001)));background-image:linear-gradient(to right,rgba(0,0,0,.5) 0,rgba(0,0,0,.0001) 100%);background-repeat:repeat-x}.carousel-control.right{right:0;left:auto;background-image:-webkit-linear-gradient(left,rgba(0,0,0,.0001) 0,rgba(0,0,0,.5) 100%);background-image:-o-linear-gradient(left,rgba(0,0,0,.0001) 0,rgba(0,0,0,.5) 100%);background-image:-webkit-gradient(linear,left top,right top,from(rgba(0,0,0,.0001)),to(rgba(0,0,0,.5)));background-image:linear-gradient(to right,rgba(0,0,0,.0001) 0,rgba(0,0,0,.5) 100%);background-repeat:repeat-x}.carousel-control:focus,.carousel-control:hover{color:#fff;text-decoration:none;outline:0;opacity:.9}.carousel-control .glyphicon-chevron-left,.carousel-control .glyphicon-chevron-right,.carousel-control .icon-next,.carousel-control .icon-prev{position:absolute;top:50%;z-index:5;display:inline-block;margin-top:-10px}.carousel-control .glyphicon-chevron-left,.carousel-control .icon-prev{left:50%;margin-left:-10px}.carousel-control .glyphicon-chevron-right,.carousel-control .icon-next{right:50%;margin-right:-10px}.carousel-control .icon-next,.carousel-control .icon-prev{width:20px;height:20px;font-family:serif;line-height:1}.carousel-control .icon-prev:before{content:'\2039'}.carousel-control .icon-next:before{content:'\203a'}.carousel-indicators{position:absolute;bottom:10px;left:50%;z-index:15;width:60%;padding-left:0;margin-left:-30%;text-align:center;list-style:none}.carousel-indicators li{display:inline-block;width:10px;height:10px;margin:1px;text-indent:-999px;cursor:pointer;background-color:rgba(0,0,0,0);border:1px solid #fff;border-radius:10px}.carousel-indicators .active{width:12px;height:12px;margin:0;background-color:#fff}.carousel-caption{position:absolute;right:15%;bottom:20px;left:15%;z-index:10;padding-top:20px;padding-bottom:20px;color:#fff;text-align:center;text-shadow:0 1px 2px rgba(0,0,0,.6)}.carousel-caption .btn{text-shadow:none}@media screen and (min-width:768px){.carousel-control .glyphicon-chevron-left,.carousel-control .glyphicon-chevron-right,.carousel-control .icon-next,.carousel-control .icon-prev{width:30px;height:30px;margin-top:-10px;font-size:30px}.carousel-control .glyphicon-chevron-left,.carousel-control .icon-prev{margin-left:-10px}.carousel-control .glyphicon-chevron-right,.carousel-control .icon-next{margin-right:-10px}.carousel-caption{right:20%;left:20%;padding-bottom:30px}.carousel-indicators{bottom:20px}}.btn-group-vertical>.btn-group:after,.btn-group-vertical>.btn-group:before,.btn-toolbar:after,.btn-toolbar:before,.clearfix:after,.clearfix:before,.container-fluid:after,.container-fluid:before,.container:after,.container:before,.dl-horizontal dd:after,.dl-horizontal dd:before,.form-horizontal .form-group:after,.form-horizontal .form-group:before,.modal-footer:after,.modal-footer:before,.modal-header:after,.modal-header:before,.nav:after,.nav:before,.navbar-collapse:after,.navbar-collapse:before,.navbar-header:after,.navbar-header:before,.navbar:after,.navbar:before,.pager:after,.pager:before,.panel-body:after,.panel-body:before,.row:after,.row:before{display:table;content:" "}.btn-group-vertical>.btn-group:after,.btn-toolbar:after,.clearfix:after,.container-fluid:after,.container:after,.dl-horizontal dd:after,.form-horizontal .form-group:after,.modal-footer:after,.modal-header:after,.nav:after,.navbar-collapse:after,.navbar-header:after,.navbar:after,.pager:after,.panel-body:after,.row:after{clear:both}.center-block{display:block;margin-right:auto;margin-left:auto}.pull-right{float:right!important}.pull-left{float:left!important}.hide{display:none!important}.show{display:block!important}.invisible{visibility:hidden}.text-hide{font:0/0 a;color:transparent;text-shadow:none;background-color:transparent;border:0}.hidden{display:none!important}.affix{position:fixed}@-ms-viewport{width:device-width}.visible-lg,.visible-md,.visible-sm,.visible-xs{display:none!important}.visible-lg-block,.visible-lg-inline,.visible-lg-inline-block,.visible-md-block,.visible-md-inline,.visible-md-inline-block,.visible-sm-block,.visible-sm-inline,.visible-sm-inline-block,.visible-xs-block,.visible-xs-inline,.visible-xs-inline-block{display:none!important}@media (max-width:767px){.visible-xs{display:block!important}table.visible-xs{display:table!important}tr.visible-xs{display:table-row!important}td.visible-xs,th.visible-xs{display:table-cell!important}}@media (max-width:767px){.visible-xs-block{display:block!important}}@media (max-width:767px){.visible-xs-inline{display:inline!important}}@media (max-width:767px){.visible-xs-inline-block{display:inline-block!important}}@media (min-width:768px) and (max-width:991px){.visible-sm{display:block!important}table.visible-sm{display:table!important}tr.visible-sm{display:table-row!important}td.visible-sm,th.visible-sm{display:table-cell!important}}@media (min-width:768px) and (max-width:991px){.visible-sm-block{display:block!important}}@media (min-width:768px) and (max-width:991px){.visible-sm-inline{display:inline!important}}@media (min-width:768px) and (max-width:991px){.visible-sm-inline-block{display:inline-block!important}}@media (min-width:992px) and (max-width:1199px){.visible-md{display:block!important}table.visible-md{display:table!important}tr.visible-md{display:table-row!important}td.visible-md,th.visible-md{display:table-cell!important}}@media (min-width:992px) and (max-width:1199px){.visible-md-block{display:block!important}}@media (min-width:992px) and (max-width:1199px){.visible-md-inline{display:inline!important}}@media (min-width:992px) and (max-width:1199px){.visible-md-inline-block{display:inline-block!important}}@media (min-width:1200px){.visible-lg{display:block!important}table.visible-lg{display:table!important}tr.visible-lg{display:table-row!important}td.visible-lg,th.visible-lg{display:table-cell!important}}@media (min-width:1200px){.visible-lg-block{display:block!important}}@media (min-width:1200px){.visible-lg-inline{display:inline!important}}@media (min-width:1200px){.visible-lg-inline-block{display:inline-block!important}}@media (max-width:767px){.hidden-xs{display:none!important}}@media (min-width:768px) and (max-width:991px){.hidden-sm{display:none!important}}@media (min-width:992px) and (max-width:1199px){.hidden-md{display:none!important}}@media (min-width:1200px){.hidden-lg{display:none!important}}.visible-print{display:none!important}@media print{.visible-print{display:block!important}table.visible-print{display:table!important}tr.visible-print{display:table-row!important}td.visible-print,th.visible-print{display:table-cell!important}}.visible-print-block{display:none!important}@media print{.visible-print-block{display:block!important}}.visible-print-inline{display:none!important}@media print{.visible-print-inline{display:inline!important}}.visible-print-inline-block{display:none!important}@media print{.visible-print-inline-block{display:inline-block!important}}@media print{.hidden-print{display:none!important}}.tm-tag{color:#555;background-color:#f5f5f5;border:#bbb 1px solid;box-shadow:0 1px 1px rgba(0,0,0,.075) inset;display:inline-block;border-radius:3px;font-family:"Helvetica Neue",Helvetica,Arial,sans-serif;font-size:13px;margin:0 5px 5px 0;padding:4px;text-decoration:none;transition:border .2s linear 0s,box-shadow .2s linear 0s;-moz-transition:border .2s linear 0s,box-shadow .2s linear 0s;-webkit-transition:border .2s linear 0s,box-shadow .2s linear 0s;vertical-align:middle}.tm-tag .tm-tag-remove{color:#000;font-weight:700;margin-left:4px;opacity:.2}.tm-tag .tm-tag-remove:hover{color:#000;text-decoration:none;opacity:.4}.tm-tag.tm-tag-warning{color:#945203;background-color:#f2c889;border-color:#f0a12f}.tm-tag.tm-tag-error{color:#84212e;background-color:#e69ca6;border-color:#d24a5d}.tm-tag.tm-tag-success{color:#638421;background-color:#cde69c;border-color:#a5d24a}.tm-tag.tm-tag-info{color:#4594b5;background-color:#c5eefa;border-color:#5dc8f7}.tm-tag.tm-tag-inverse{color:#ccc;background-color:#555;border-color:#333;box-shadow:0 1px 1px rgba(0,0,0,.2) inset}.tm-tag.tm-tag-inverse .tm-tag-remove{color:#fff}.tm-tag.tm-tag-large{font-size:16.25px;border-radius:4px;padding:11px 7px}.tm-tag.tm-tag-small{font-size:11.049999999999999px;border-radius:3px;padding:2px 4px}.tm-tag.tm-tag-mini{font-size:9.75px;border-radius:2px;padding:0 2px}.tm-tag.tm-tag-plain{color:#333;box-shadow:none;background:0 0;border:none}.tm-tag.tm-tag-disabled{color:#aaa;background-color:#e6e6e6;border-color:#ccc;box-shadow:none}.tm-tag.tm-tag-disabled .tm-tag-remove{display:none}input[type=text].tm-input{margin-bottom:5px;vertical-align:middle!important}.control-group.tm-group{margin-bottom:5px}.form-horizontal .control-group.tm-group{margin-bottom:15px}.c3 svg{font:10px sans-serif;-webkit-tap-highlight-color:transparent}.c3 line,.c3 path{fill:none;stroke:#000}.c3 text{-webkit-user-select:none;-moz-user-select:none;user-select:none}.c3-bars path,.c3-event-rect,.c3-legend-item-tile,.c3-xgrid-focus,.c3-ygrid{shape-rendering:crispEdges}.c3-chart-arc path{stroke:#fff}.c3-chart-arc text{fill:#fff;font-size:13px}.c3-grid line{stroke:#aaa}.c3-grid text{fill:#aaa}.c3-xgrid,.c3-ygrid{stroke-dasharray:3 3}.c3-text.c3-empty{fill:grey;font-size:2em}.c3-line{stroke-width:1px}.c3-circle._expanded_{stroke-width:1px;stroke:#fff}.c3-selected-circle{fill:#fff;stroke-width:2px}.c3-bar{stroke-width:0}.c3-bar._expanded_{fill-opacity:.75}.c3-target.c3-focused{opacity:1}.c3-target.c3-focused path.c3-line,.c3-target.c3-focused path.c3-step{stroke-width:2px}.c3-target.c3-defocused{opacity:.3!important}.c3-region{fill:#4682b4;fill-opacity:.1}.c3-brush .extent{fill-opacity:.1}.c3-legend-item{font-size:12px}.c3-legend-item-hidden{opacity:.15}.c3-legend-background{opacity:.75;fill:#fff;stroke:#d3d3d3;stroke-width:1}.c3-title{font:14px sans-serif}.c3-tooltip-container{z-index:10}.c3-tooltip{border-collapse:collapse;border-spacing:0;background-color:#fff;empty-cells:show;-webkit-box-shadow:7px 7px 12px -9px #777;-moz-box-shadow:7px 7px 12px -9px #777;box-shadow:7px 7px 12px -9px #777;opacity:.9}.c3-tooltip tr{border:1px solid #ccc}.c3-tooltip th{background-color:#aaa;font-size:14px;padding:2px 5px;text-align:left;color:#fff}.c3-tooltip td{font-size:13px;padding:3px 6px;background-color:#fff;border-left:1px dotted #999}.c3-tooltip td>span{display:inline-block;width:10px;height:10px;margin-right:6px}.c3-tooltip td.value{text-align:right}.c3-area{stroke-width:0;opacity:.2}.c3-chart-arcs-title{dominant-baseline:middle;font-size:1.3em}.c3-chart-arcs .c3-chart-arcs-background{fill:#e0e0e0;stroke:none}.c3-chart-arcs .c3-chart-arcs-gauge-unit{fill:#000;font-size:16px}.c3-chart-arcs .c3-chart-arcs-gauge-max{fill:#777}.c3-chart-arcs .c3-chart-arcs-gauge-min{fill:#777}.c3-chart-arc .c3-gauge-value{fill:#000}span.twitter-typeahead .tt-menu{min-width:250px;padding:5px 0;margin:2px 0 0;list-style:none;font-size:14px;text-align:left;background-color:#fff;border:1px solid #ccc;border:1px solid rgba(0,0,0,.15);border-radius:4px;-webkit-box-shadow:0 6px 12px rgba(0,0,0,.175);box-shadow:0 6px 12px rgba(0,0,0,.175);background-clip:padding-box}span.twitter-typeahead .tt-suggestion>p{display:block;padding:3px 20px;clear:both;font-weight:400;line-height:1.42857143;color:#333;white-space:nowrap}span.twitter-typeahead .tt-suggestion:focus,span.twitter-typeahead .tt-suggestion:hover{text-decoration:none;outline:0;background-color:#e8e8e8}span.twitter-typeahead .tt-suggestion.tt-cursor{background-color:#f8f8f8}span.twitter-typeahead{width:100%;height:30px}.tt-suggestion{max-width:25em;overflow:hidden}.tt-suggestion .tt-label{padding-left:1.5em}.tt-file-header,.tt-suggestion.tt-match.file{background-size:1em;background-repeat:no-repeat;background-position:5px 5px}.tt-match.predicate.built_in .tt-label{color:#00f}.tt-suggestion .tt-title{color:#555;white-space:nowrap;overflow:hidden;font-style:italic;font-size:80%}.tt-suggestion .tt-tags{max-width:100px;float:right;margin-right:2px}.tt-suggestion .tt-tag{max-width:30px;border:1px solid #ddd;padding:0 4px;margin-left:2px;border-radius:5px;background-color:#e1edff}.tt-suggestion .tt-line{white-space:nowrap}.tt-suggestion .tt-lineno{display:inline-block;width:40px;min-width:20px;font-family:monospace;color:#999;background-color:#eee;border-right:1px solid #ddd;padding:0 3px 0 5px;text-align:right}.tt-suggestion .tt-text{padding-left:5px;white-space:nowrap}div.tt-file-header{padding-left:5em;background-color:#ddd;color:#000}span.tt-path-file{font-weight:700}div.tt-match.source{overflow:hidden}table.diff{width:100%;border-collapse:collapse;border:1px solid #a9a9a9;white-space:pre-wrap}table.diff tbody{font-family:Courier,monospace}table.diff tbody th{font-family:verdana,arial,'Bitstream Vera Sans',helvetica,sans-serif;background:#eed;font-size:11px;font-weight:400;border:1px solid #bbc;color:#886;padding:.3em .5em .1em 2em;text-align:right;vertical-align:top}table.diff thead{border-bottom:1px solid #bbc;background:#efefef;font-family:Verdana}table.diff thead th.texttitle{text-align:left}table.diff tbody td{padding:0;vertical-align:top}table.diff .empty{background-color:#ddd}table.diff .replace{background-color:#fd8}table.diff .delete{background-color:#e99}table.diff .skip{background-color:#efefef;border:1px solid #aaa;border-right:1px solid #bbc}table.diff .insert{background-color:#9e9}table.diff th.author{text-align:right;border-top:1px solid #bbc;background:#efefef}.notebook{position:relative;width:100%;height:100%}.nb-content,.nb-toolbar{width:100%}.notebook.hamburger .nb-toolbar{display:none}.nb-toolbar{position:absolute;padding-top:5px;padding-bottom:5px;margin-bottom:1em;border-bottom:1px solid #ddd}.nb-toolbar .action-fullscreen{right:5px;position:absolute}div.notebook-menu{display:none}.notebook.hamburger div.notebook-menu{display:block;position:absolute;top:3px;right:1em;z-index:2000}.notebook.hamburger .nb-view{top:0;height:100%}.nb-view{position:absolute;top:40px;height:calc(100% - 40px);width:100%;overflow-y:auto}.nb-content{position:relative;width:100%}.nb-bottom{width:100%;height:30%}.dropdown.cell-type{display:inline}.nb-cell.markdown:not(.runnable){background-color:transparent;border:0}.nb-cell.html:not(.runnable){background-color:transparent;border:0}.nb-cell{margin-left:20px;margin-right:10px;box-sizing:border-box}.nb-cell:focus{outline:0}.nb-type-select{padding:1em 0 1em 0}.nb-type-select>label{margin-left:1em;margin-right:1em;position:relative;top:.1em}.nb-type-more{padding-bottom:1em;padding-left:1em}.nb-type-more label{margin-right:1em;position:relative;top:.1em}.nb-type-more input{display:inline}.nb-cell .close-select{font-size:150%;padding:0 5px;border:0;color:#888;background-color:transparent;float:right}.nb-cell.active{margin-left:8px;border-left:7px solid green!important;padding-left:5px}.nb-cell.html.active>div.editor,.nb-cell.markdown.active>div.editor{border:1px dotted #888;border-radius:5px;margin-bottom:5px;margin-right:52px}.nb-cell.singleline div.editor{height:2em}.nb-cell.singleline .CodeMirror-hscrollbar{height:0}.nb-cell .CodeMirror-scroll{max-height:40em}.nb-cell .CodeMirror{border-radius:5px}.nb-cell .nb-cell-buttons{display:inline-block;float:right}.nb-cell span.glyphicon-cloud{color:#000}.nb-cell.background span.glyphicon-cloud{color:#fff}.nb-cell>.with-buttons{background-color:#eee;border:1px solid #ccc;border-radius:5px;width:calc(100% - 50px)}.nb-cell .nb-query-menu{display:inline;float:left}.nb-query-menu button{background:0 0;padding:3px 5px 0 5px;border:0;color:#888}.nb-query-menu button:hover{color:#000}.nb-cell .prolog-prompt{float:left;padding-right:.3em;padding-top:.25em;font-weight:700;text-align:right}.nb-cell .editor.query{margin-left:44px}.nb-cell.program,.nb-cell.query{margin-bottom:1em}.nb-cell.not-for-query{opacity:.5}.nb-placeholder{opacity:.5;width:90%;margin:auto;margin-top:1ex}.nb-cell.markdown pre.code{width:90%;margin:auto;margin-bottom:1em}.nb-cell.markdown dl.termlist{margin-left:5%}.nb-cell.markdown dl.termlist dd{margin-left:2em}.nb-cell.markdown .predicates dd{margin-left:2em;margin-bottom:1ex}a.btn-image{padding:1px 2px}.nb-cell.program span.image-icon{display:inline-block;width:18px;height:16px;padding:0;background-repeat:no-repeat;background-size:100% 100%;vertical-align:middle;background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAKAAAACgCAMAAAC8EZcfAAAAIGNIUk0AAHomAACAhAAA+gAAAIDoAAB1MAAA6mAAADqYAAAXcJy6UTwAAAAzUExURf39/dXS0qShoevY2vf09P38/Me0tGNfXzEvLwUBAS0FA14LBJ8TANAdAfklAYp4d////6nIvA0AAAAGdFJOUwD//4heJmPUefMAAAABYktHRBCVsg0sAAAACXBIWXMAAAsTAAALEwEAmpwYAAAAB3RJTUUH4AkVCzYIO9WCWAAABddJREFUeNrtXdmS3CAMBHxw2///t0Gy59yxwUYcD1FtqpKqTW1Pi24kkL2M/Y//kRSc8zmECH/CX3vDJoSQUqo9pByEmDtByWfAppT+igBz6AAkF8P4wmbClzHvKANI3pK8QW7oAixrrXuFtQ+gSopGNAJ5GzqA5r1fXhH+5QPKHaRqQSPng9rQBXDL7wCQG0Y1zHUh6vkJ7wjdE6O1O8Sa9A0SiLHWn8PbQe4Q6+V5y65xLgXeRiMmWgpdA57C9BqbiO7BIkBUK68hXqDPukv4QjhbJ818p+8qvkAi5lny0vhw9V2H9yRRFlUzB/Vat9wMj2meS+KD5eeX5T5CUxLhhs8tOVESIR9MHn9PDssoBfWbiw84LKVl8D/jloUEoaDHNwM+T4Bv07IoIRAS/sAPQSi8QIKdX+gQDhM5PkuFr8AypEwwLkPqJINCCPGFJAcKB9oSgTDBe5IJKRQXCPT4Ff82sOvaBGKrid1xQrlISWFYgQkK8c8+OPTx8YobdEK0CieRQKDHavQVJlr10FEIHhMj5AveBtFHV6GgkkhsE3ZG68sIgcKJiMDIj/qJL1p8gxdS5HgeYx5zhC+CkEomIqZhb/Vh2LP/aGisUKSk6ihOP5oj0XFUw96cADylkEbH0SVo9Wm4848mii/BcwLPKbQUizAAPF2C7hyfNhEnLL7PRTJ8mmMKlWAls5QDmG3V0X3EZACkkDGP1Ko+h0EKGfMxso9EAdpz+nMBRtulHAYXgt04uhO3BjjnAjS+OMDzFLvYTuIbM+jv78U0Ko62xO5+hoHBNZdBGQN4TqEt3TcltHTu7gpEgDPFXhzr6e4V1ERt0xoHeJxkF/1k+TV/Qld8hDB6ZUZSsCYdzGy3rdfyu7kMAUCZcvTm/559xG9EaXqS1LM39wHRpFwo07SdTJjE+5FtEAVHaNKmBShakuTTwdcRpveJt91URx9Y9C8FwlGdvwmqO7CjE0ytS9cLt+9KVgoCS1xCbBk2VPMLKZvJLQKpbsOKyCRIxHCqSSShSG/qdgKNZIqKwoGcwrACjRjp7sI0MYWE1zhPpyEVMqzAeSREKGi9cFuBlHfuCZclF2cCaAkknlnwhvAu9n0owJPtwkZxaoQ4VkG3Aukne8ALyQZ7jBQTPUIqq4HZ6gKjUejWFDqBHlUVmQfmI0mSA4FGKFaEQgqdYJ06lgFIMX/k0WJGVibmfJ2AQlZWLLJnzHAPmadiAMEMlctJcPDooqPemUmGImFlRWNQtwfRdwvkqijALCUHBZviz71kJDkoWM1jaYB6uEuhDw6jajxQcrcyxEaOVYibZogWXeWxpknoGx0UWKCq9GQYdlCu1wTfLGvAomXF59auKhktuuKjf5eV7Ir0SZHy314sYqo+3Xltx6up4Fs9XoUiJussBBvhglVqtk5Cgu3MqkdyWYMJnuoDZKlm2EAhr0Y+gcLqFviKNeXYFapA2ehVBkk6wdNo1ijmuNXA5JTUrQCq+JkhnHQ0I3C3mhiBK2sYkRueoJCmBEavJ+AssCmBEQqhTJWNX+hy6tYNPfrNrc2hW+OFV3OAJ4UhXnix5nHYJeMmp9oDPBRyIFAJxrqlEFbg0AO+IwoDgbaT12/99EL0QNUHQP5rR4ZNZGasHwr9n0LfyG5esPaDwk488K3s+qLQGi07ekMdV+bTacCk0wmsUHFL8+k0LvW8XNdpmDUMurqrJl2vVdGYY3vBY+q3Uev7rPBpoap1Ix2bV479UaWvGwr5XSY/T2N0Y6d5l8n3QwStsW1WaJ9F10cr0gW4R47NE+AmkX7AoUweOfalJouy69Z9u+ui2TzKsd8l0kud8LHI9nlwcOmhRwIfVSHFs2iF2BT4yL1VelxZnxQG7nzIsBK6T4B4IgxHlpx1GngTr6uMdqTGZz0MR9admYz+k2NNPyJ9E9v022j6MJkjlQ740t9uNbIddHXVD//M8cA6Byg6BghO2PMSRJX0DTCUXHLqGSDr7rcuVIh/P/O/AARSDtsAAAAASUVORK5CYII=)}.nb-cell.program.background span.image-icon{background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAADAAAAAwCAYAAABXAvmHAAAABmJLR0QA/wD/AP+gvaeTAAAACXBIWXMAAAsTAAALEwEAmpwYAAAAB3RJTUUH4AkUDTkUFH3ZDwAABydJREFUaN7tmWuMVdUVx38zMjgMMIioW54iUsaKSI3FJ5vWx0SMlmhVGhuIMdE2VasmRrObRkinsd1RU2kbDdSmEfGF+KhK0mBBhQ02PqZVqYIoIDMoblAcxlauysztB/+nObm95z5mbtsPzkpu9j1nr7PPWnuv9V+PAwM0QF9tqqvFIsaHEcAxwOnALOAEYAIwRCw5oBPYCKwF1gPvRmf3/l8VMD6MBO4GzgOGAQdV+Ggv0A08B1wRnd33P1XA+DAa+ClwjW71ABuADmCe7r0InAL8E3gW+A5wAHhQpzMLqBfv7wAfnd1erSz1fRD+MuD9lPC/BQ4Bzges7m2QgAD10dk5wGpgEHAJMBs4GPiVeH4AvGV8mPtfVcD48AftIMA9wPjo7HXR2X8AjwFHAe3R2ZkS8N8UnW0FVgFNwOro7IHo7I3AaGAx0AAsNz7cX3MTMj4cLDM4XfZ7YXT26dT8z4AFwKfA8Ohsr/FhGPAJsD862yS+ZmCzhL45Ont7ao0ZwBpguJx9enQ2X6sTWCPh9wBfKxD+UMABXwA2OtubtUh0thv4li5vk9DJ3MvAccAWYBqwriYmZHy4BzhDuzsuOrutgOUZYDDwQHT2r+XWi86+DdysS18w/R4wA9gHzDQ+PNIvBYwPFwFX6vIg4JcF8+cDJwG7orNXVGG6v1FsOMv4cFZKuTxwA9CoW5caH+b1yQeMD4cDu3W5AviulNipHXxajtsKXB6dXVbw/H/4QJHNeVyINlXrLALGiGU1cI4UHRmdzVV7AjdpXBadnQtMBN4AxgEPSLlW2f5D1cJfdPYJOesYYBewXP+3Cd1agUd1GiurOgHjQyOwX5eTo7NbU3MXAD8Slicb8I6w/1X93wl8BrypHRwPjNVvMjBdftWSCoRrgMVSLHnXYAFHI3BssUCXpcDdEvL+6Oz8DFjdK6zP6QX1VUT2vOA4BwwFuqOzIzJkWaJAtzA621bWhIwPTUASEa/PEOB4IU97dHaYri8CbpEpvAjsSAm7HXhJvrRAvCfo2feAZuPDNzLetUjjT4pNDipy72igGWgHPs5YdKqe3SB73qwA9WRqI+plGrno7KQSp7EEaFMO9WoRX9lkfOgAJhgfZkZn15dz4ukK6y+XiIRnaCyF+00VmtNyja0leH6tcW4lKDRT4wslFkyOe3MNyolOIdlI+VYxekrjyZUoME3jxhIvnaxxRw0U6AU+FBBknVqXULG5LAoZH95VVjktwwe69UN5fVbuMxR4S0gzNlWdFVKDEsVRypP2FOFpVhXXHZ09upwTN1dwAgl1VMDTCHxU4Wn8rcz84EpQKG2b+Ywjn5gyoboSedY4rdFRgq8OOFKy7FLVVmyt0UK1sgp8DIwEpkZnP8kILnlB3MQSudQgOWeuFJ94N0nAqdHZrozA2ancqqwTJ47ZUuKdXVp4VBnTqbRYapayWbnZcPHsr0SB11PxIIu2pZy4v1QPHCZn/zSD53ClLV2VKPB8QbAqRknEPLYGCoyRc3ZnpczApRrXV6LAJmWSM4wPWY6XBLkTM8xiKGASJzU+jFB9UIwuTpWtWZR0QB6qxIm3C+ePB44AYhGejUKE0yTweOUycxSl05lpo7A9b3zo0bMrgaXR2Q5lvWTVFMaHUyXHh9HZ18qeQHT2c7VMAJZl7Mjf5XSnGB86BZO/AE6VwL2pgNQLfCCFhygdaAN2GB/eTyA5OvuXMrvfVm1J2SMFT0qKdUHjBcDSVMDLS9gVKjHXRWd7hC65grZKnZpfFwPfBw5NbeJnwGXAk0lnQ6l9F/A58PXobGc1gewW4Fbt7Gx15Bam4LVdBX0OGBudPVAkRSg83bzaJeuA64X/LargxqtG3mp8aIvO3ie/aFDHo7PamvguBY5zjQ9r1ZFrEYS2Rme/KUEaVaBU26K0QrG90dkJQr03gUnAUuPDDpnkvlIdj/oSRfe+VGo9S/nMbGBKdHZ1qi9aB9xZpfANwB91OV/ve0Ft+VaVq0mMmdfnvlB09nXg56nCe0t0tic1/6iK+LHGB1+FDlfJ/l+Kzv4ptV4PsDWVgy2Ozq7sV2cuOrsAuFdQ9prxoaVIdZYHbjA+TKpg90fJPEl16JK5KWotjgIeAa6uRWuxTja4VDnJZuPDNSkFdwN3KNQ/o1ZIqbznlaRYj86uTc1dpQqvAVgenf1eJc3duipt9ybgNl1uAb4NfBCdzRsf3lBzdj1wppy7sDv9mDp87cDJ6mI38+Vnp6RMvSs6e21N2+sFSpwJ/F5o0asW4xLgz/KHoxQT5gnbc9HZIcaHZbq3G5iigPbDVCqxB5gfnV1V8+8DGYoskjM2pSLuKr78XpbkNmcrEK0QL7LtOal0uxu4Lzr7477I0d+PfIcJ9haWqR+K0dsKkquis7v6KkNNPrNKmSOVCpyt6qopFY2/UDESdTIPR2d3MkADNED9pn8BvSyBlToydnoAAAAASUVORK5CYII=)}.type-icon.pl{background-image:url(../icons/pl.png)}.type-icon.swinb{background-image:url(../icons/swinb.png)}.type-icon.select{background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAEAAAABACAMAAACdt4HsAAAAIGNIUk0AAHomAACAhAAA+gAAAIDoAAB1MAAA6mAAADqYAAAXcJy6UTwAAAEUUExURTAwMDQ0NDQ0NHFxcX9/f7Gxsc/Pz+np6ebm5vf39/b29tra2pCQkN3d3NLS0p6entnZ2cDAwEJCQuvr6+Xl5dnZ2fT09F9fX93d3ZqamtjY2K2trbe3t8fHx8nOw/Dv7rjDqKS8iJ63gZO4Zoe4Sn23OIq4U6y9lr7GsqnBiXi7Jn7CKpLKSp7QY53FaabUbZfLVs7SyKrLeYvHQoK/OMTKuazZc6PaWZzUVojLM4PHLbO/pI3SNqC+erHedrnWh7bGmeHi29TXycHLprDda8TZmqHJZ7zVlM7WttHZubLJieDf25baPLXjeZjXRq3iaJ3iQZvgP6XqR7Hja6zyTafjV8rYqbD2T7P5UrTvX67Clf///2wKwGIAAAAedFJOUwIXJ0JJaqba///pylP+nGHghjHqt6zfOula2HJ5ovRUycgAAAABYktHRFt0vJU0AAAACXBIWXMAAA3XAAAN1wFCKJt4AAAAB3RJTUUH4AkVDAIvILrSQQAABcRJREFUWMPNVwtb2koQJRuoy7ZBkRa5bS9JQQUJyEsegRQfKFUJNMRQrP//h9yZ3U0M9dl+97vfHSBiyDlzZmZ3djcW+3+bEl7+lEBBuKIof4QlMULgShRO81skChriAU2IqvAvyKC8Lm4OJwIej8P/RDK8ToVAK2rizcYGTYKx/Ns3iYDhJQoS4/D4uw0NsUkdX2gbKVXIgMieZ0D8JvcsTTIkk1vpbQzqeTjau40Qq7NMhuk6RQYgfR9/iQAZArhmfCkUd/d294uFUlmTKlLo4akgRPQCT42D3QraHr9W9gtlquPrg/p0IpEgIbyXiyZgq7XaYb1+2Kju7lXMSmELCCjN82Q+Vb13HN4sALpRP6y36oHV2qa5V8hSyIa2EydPlT+hc/f7FbNxj5U0tSPTLHZAg56LPyoB/McZ4o29SkNCu/yD13qv37AGlX0Dw3irkkcSocj8DSsBHoBdQdGwjo4G5lFlMDgaYhQfyEMGKHBK+DdrQjS4bnXBGvZAmIkXqwOJ1CEI5eEAwATk22ZD6u5y61scbA0CK+YoTWrb6xIUnPkoQCsGeGH1xuHXqoUmSPBPgYGGze31GMC/igGUzHY9AI+6xycdjZ2ejUu2JQ0oLMsAAooS1lOIArL7Zk3Cu+fdizMqjHUmtmUP8I0ERQ1u/bWWBRSQhalTMqvSeXc0+pbhI48zXFZtaZaUUFhPIx/DOmuYUv9oNOpe4aChjHGKcYBHiq9w71SNxqAQNQUCymY79D+6xjmcua5NxkgwnTh2KMLOM8rSkTrgJM/rGEFfEIxGs3kZOgBtAczpoJCW7dhOQDIEXYW1QipxEECLplAP9t2+BsbO3AE7QQnX+C3g+AJp+ahEkgDTAAjO2uaxwM9Gjt0v02yLo8b3BJzEtotTRpORQkIREuAvb7Wl/1kPXLk17t+ZX8Fv08nCWYQcjQxlyZ2QAFeQtI45nHOCGQrgDy4ANR9jNcaAdgMJTrUJt3bWFKQhBMPsA/wYCHoc7wKB646xGV72XA++BxqqW1DISBmglXyCHBpWn/ufzeRzruN6mEv97NxFW7gLMPxl65RBHUlkGHyGxwxrLvA3HM0twHuu63mCBSjmHcYym2FfwmaWTlK9Y7UhfCDo8fDhYa83hTmeOffQXHwJgn6W0akatnck2IEQ8m17NhMRoFR0d4GLy8gLTUqYaIwxNRICxAAKMg27yyNwBRwA32CKXiLS9wIVSNGaMtaMNFZs6Dhwv9g9mQJB4HrLS3p17vu+xz9CA7xhKLNCZHlAghSsOoY9R4KlI+Ho+WbpCwOOMIwOnbLNaGvHJQmGa7Pq3CCBKICLwo9/XPj3xkW43iQz5SmIxqCoWYjBaPdns+NlgPd8yIF+sVrdgq38QII3pIxurPU0rEMhSWmHS3AXEu/5l5DEH/cEgmOSg9mcWutISBAHAnbtzGfHtwuZAV8Q3HJbrVYyBkyhrpK1roo7lwJMkGbD+TnzAwGeB+MgeXEbMAgBrSwQpH5ZWbgErORw7nxfLgIC/+bq9OpnlMD3egZjyQz5tatjJd9gC71znCUPAYuAdhsaJ1gaUIHk54drIy7OOZik2oETDEMPa7+6XUVy4HslHMW57Yd4bAqb2MLPDuZumASAAPC+jMvSFPE75NEdI7QVoKdaaR4m0ZcMwr1/jgVgGfWJjRbc/hs0MGZMnEgQnIRfu2XEs7RKntjjqMiAYTTv+nIuhBS+XzeaGihsph/fY/FNNpFRnLL8Xd8L48Dh0z1poncqGhF5Zp8ahw0ErFwsY9zVJ0skWJ4fnJQzXD0bqs/gg3U6RdEVZqvZKRvlcqeJaFCmaWkcss/iuYp4SscxtW56UvvM95gkFnt5v72Zyv1KkEupr0CHIiCb6Y8Ag20Tyh+mdwh5Ifo1EZxEVbYTiU/pdFwoF/DXMUgRJECK0xv5vWMficljX4wQ5c9OjjF5zBLnxn/hCPwfI19t/wAe25dChuNuFgAAAABJRU5ErkJggg==)}.type-icon.chat{background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAEAAAABACAQAAAAAYLlVAAAAAmJLR0QA/4ePzL8AAAAJcEhZcwAACxMAAAsTAQCanBgAAAAHdElNRQfhBAMNASzV4qVYAAADQElEQVRo3u2ZS09TURDHf31iW4G23PJoRI0hPkLqAhM1PgILSPADGNyZuDDi0gSJiSsTXfgJXOrCkBiNqDvCgqiRaGJ8BRoTdCE+8EFAlFKQclxQSkt7T+9pe+rCztn09jH//5mZM3NmChWpyP8uNpP3XQT5mnpyUoUbH1sJY+Bljlk+84F5llhkOakpyBx/cuhyYKTpskTAw2a+J1/voZX9HCBCIOt7M7zhKc8YI4oXwUIOXU78zJBQsYqXQJJYD3eZQORdE9zjZE5dDgycak5xY2ADuomyZAF8bS0RpTvLvmEcqvCNwDaGFKDT1xDb03bfZBpjpsavw84ZZguEFwhm6cUBuDBUd++lBgcDJIqAFwgSDOAmiEvV+EG8vCgSfG29plrd935GSgQvEIzkOLYS4xs4uV5CeIHghtUD6CEA9JUYXiDoswLvIgRENMALBJH8BBoAGNdEYDy5yTzSy7ImAsucwU6dHN7PQ03wAsEozbJ8aAfaaNNY8CPsRMgIODiKTyMBH0dkKdmOh07Nl55OPLKPA8Q1RoBAEJflRDv1VGm2QBX1MgItZbh5tsgIhMpAICQj4C4DAZeMQKwMBBZkBKbLQOCTjMBkGQj8kBH4yDfN8NNyAos80UzgEbMyAnGGNRMYJi4jIBhlSiP8FKOyargqgxorwaC1ejWvCT5GlzVD3dZE4I5VT/mZ0gA/ab05qedQyS+mKxy0OqYJ4QJOs1JS+LPWmnMbgdSV6UrRnfE6/FWrxq/Dm/Z0rkQE+gut1Ta6+Fkk+G+ObTB+g1ru2sHzggMywSt25YwwJanlIm8LiIcJLkkizKKsDdb2Kk6KopzPcfk0MiLM0ploSvYxHUr5vgs/9ixtjao3TjvhVPgMZYVWLz4uM0ecBWLM84sxrtFj0vvaCKnCOwmldtGRlVRPpNqMdtppoznV++XLLoq+X60M7zLgH5v0zwFqTDsBT6G+Bxf3M+BvYpgUMLOuWtn3jpTvnYR5kJZQY1wwbbtrTbZiqPt+fah6PC0FfeEW+0x+U21SaG0EVA9e5kB9N+8RCF7Sz2GTPULAdA6q7Hto2DC/2MIpWqlhU+pfg+w86TPVpZx0K1KRivxz+QvZxVirW3AIgwAAAABJRU5ErkJggg==)}.type-icon.chathelp{background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAEAAAABACAQAAAAAYLlVAAAAAmJLR0QA/4ePzL8AAAAJcEhZcwAACxMAAAsTAQCanBgAAAAHdElNRQfhBAMNBAMDRGxEAAADxElEQVRo3u2YTUhUURTHf29mHHWmdMY3Mo7al1CLCoJqGaUIRUXRJmglEQi5C6NdQav2UVCrIimoVatqIWRIUNIXUhNiUUlZBJnfo+OMvhaO43N89757n7NoMecuxLnv3P+599x7Pv5QkpKUxFnKiAtmwlQ7/m5gUuY44xeuJZRKagUz64kK4KOEHGcCxPDrwYeIYjjORFkv0KmlUrD7GAE9+CAxAXw1YYFOneDwDep1dx+kTuj7iND35YLdJwRb8eD7kHD3kbX53lgBX8EYluPhb6eRzTQQJUyALNOM8pOv/OI1sw4aPkxGyeodfq3DgVXRQQ/jpEiTYR4rP+bJkGaGUZ7SQdUq3/vW6nuTI3TbAN1GN0cwvfo+RGzF/1vo5IMG+NL4QCdbCevuvrLg3Xcy4AF8aXzigm7Qtfs+Qt8awJdGn+DJOoo9TrcwXQR4C4tpWlZsUklOFw1+0YTT+RtmqsC3kS4ivIVFmjaHGyaQ/UpLZrjJYZpo4ihdZBQ0WqlWgW9gzHWpGe4WXK1N9LpqTdDoDh/ggcJekgXRblHTPVTdd0/HraQUDMhyCYB9nOOk7ezc9FK0yuHLuaN4qeY4y3ssFrAYpBww2MBjV707gnSdjwPebv9lII6fawqvQVIT+mgm6KlsXUcFI1jCIs2e6Jpl012e9p9ld+55DSl83SUzIOnJgBM57VNKXydlBkxqg//mWE53J3NKGpMyAxY04Ufy8Af4rqgzLzNgStOAi/noMaKsIz2Bj5oJZlESWieXlD3DV1qP713u7xWtqu+NzIBHWgZM5KtGHXkk6wviDMlD5QoZ5y0BsuxxSE0imWMjv2W54HaRCxHNXKBXCU7Rz3v6NTRcsyH4uae83HOC1BDkhbLGA5X2PMEfxeV6chq9it+P0SCH9gEGE1xXvFAG4C9oamVynGG3csygmnS+hHaTbdygjAzblG5/O73un5kYnFGqcL32Ba6tWUirC/bSGcXditKJIsPbe0ODWnlrVsaNgsw1yOc1gA/QWUDfVcpvdSNfchYO8ZI+PvGLKQ5xhl3adWKSWzzkq+2XGClScqWrWDzjPDuIEcIgnqMXajjIE08MiZ2+Uyh4W2x8ho/6ghceop1u/jIj4IhSjNOziiNa8n1QLbAsx4QoIyw4Jqy9JGgigUkYf44lG+YbP/jIuOO6EWaZ0fGfmFQNCfmOsIAjFFO3kpNICGjFckxB4I1IqFvNZse/yvfLj7ROm7aP6cKLSdVi0vaefF882l7aHfsFh29q0/ZxVT6sJCUpyX8k/wALscSVmxSJXQAAAABJRU5ErkJggg==)}.type-icon.togetherjs{background-image:url(data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAEAAAABACAYAAACqaXHeAAAABmJLR0QA/wD/AP+gvaeTAAAACXBIWXMAAAsTAAALEwEAmpwYAAAAB3RJTUUH4QQDDQo2y3SF6QAABvFJREFUeNrtWn2MVNUV/51773sz82ZnZr8Bu8BqSVSobdKCNSmR1BYhJFX7R8UgmwJW2sQQ4xaotYltGhutUvpBIJQEkQjIEmuaSLtUA21obWpLibRrjUUoirjuLvs5n++9+9E/EKOU3Sz3bk2Tvt9fM2/ePfec3zvn3HPOGyBBggQJEiRIkCBBggQJEvz/ga50wY5H1wbTgqgu58VeICLOYUBkECmBqvbUWORH75TTY/d9Z1s4nozVP9iWirJNeeln/ZiluOICZAwIGp4MlYgrsV8ZLj317bWV/xkCntn0tfltdaUbpMJSIrrZY3q6zxQYDECAMgyxZog0e4ugX1TgfzhbzP911be2//2ijFU/fPKGcm7aZxTYQgaz2DAxSzEBTQxkAIIG0wpMx+8ag6Pg/FBQ7O95ekPHXz5yAroe76DlG582P/3+fbM/0TS8KSviz3EyMwRpAICZQKABIA2D0nRGSX3o8PmZz59ovvVLRvhLDWPtmvgH7hxfLTIKzKheIcOX8oOn1+98eN2bd27aRwfWrzAfiQd0/WjNY9fkxh7gpH0b4Qwar/FPmX+03iZPD1XFWKiILBVlRkfZUu+P93auePC/7gG7H7un8LFcravRry6xE2oQw8NLmWUIr7oJPkIQCK8PVNA7FsLl8aWj4m/84sDyPQ+uHp0KAvilF3Y+em/Tx+tLz+a9aDFZGa9RRh3+WP8VmOmfBDfx+yHTWueDEWG0Jq1JUNyfY/zMjQsW3vyrE4efr7oSwC69MKdQ6s6K6BayVDFCCscKt8E0zgG0/LDy2qCtkEJ7Qwa2oWBAiET6lnJh1qGp8IAPEdC9peNI3gsXkHU8GfSkbkLUPA8TETi7IYXGwHOK3MgL5t+15ZdHpoyAX2xeff+0dHmRsRakcZ5ace6qZRBGTnivNsC86QF8zhzygUEl3bDo7s1d9zsTsPuJtW0zgvK9lwuJyUJrg5dbV6KOTS7JcSJc15qBNk4nGqsEjWtXbdo904mAWUFxicfUPFshwsR4Jb0QmWweZpIGaQM0ZDw0Bx60AweaibmlTPOt1gQ8u3lNXoE6BdlrIUEIG6+zWttWSE1QEE0iEIgDMJ13b34mb0VA3gvrcyKeaxwS35v8WhRFq9X6wOfI+twhCgykyMyNvGy9FQHlWKxMcemQjw1UpgHaC6zW+5xQl+JOxZHiHoSsrbQiIOPpL7tsHhuBqmgEZ3aHJ2eEwOPWdcHFKkt7qTvsCOBxO4z99hGlMMBnwOVASwsG5sAAAVDMv9qKgLSQeRcP0CRQ5QWnROZxAhE55gHfLgkKMp6b9xEME27VGJFbCFw4DazsYMZAOxfUZsracxcdrOxg0jDpsi9Bg73X8blUka4UMqOs7GChFiPksD03MerksM148X2ESjuWxASu4xErAkrSO+kSgCmEaNHvQDsIqUntVA4bAELWTloRUItpv0sCYtAQ0RiUskslUhlUIsc0RADF0X4r/VszYVdVuvXm6Vo/RFy0dv9SqJxOAaEiREF9lxUBZyvZalmJIy4Tmln6FIKoz2p9MVSoxMrJAXhc/W2m1G81HmMrvrmzrA3tiDRzcAKGlsE/Wy19a7gG5lAEMS3BoXfsWd9Rtp4HHDvfclAZdtS6GYHAtbIHpeE+EE2OSEaE3rEQpUjBpQgko39fGDx10Gkg8tD3flL+V7GwTRuqWZPAfCwZ2olSPKmchZpUOHne7emTMbVcsXfrju92lqzD5+KH5148/urtixdMy4r4s7Y6CVIw5SEM5+aOaxgBkMagp7eCUGkX4xHUhrbv7bzrCaf88cEv+7pPdC9f+umWFFM32pFAaNT9GI59VLMzL9vhGQBvDFYxWIld3B6puLK1a93t61wr6P8I2NOj2Q2jUWqrtmyRGQzml19Aqu8YcEmTxInwz4EKescipyfvR+WtmdG3N0xFCzGuld1bOra3pCprmGW36JsQR70votT2eXBGUNrg1b4yBivSuvcnY+JMOPLk/nV3fGOqeqhxh3F7u/92cNGihW8X/GimAc3gVzg0VSRwtT4FGjmrTlP7mZ7+Wn40MszGeHbhLfHxXPHcw/seWP7IVDaRE04jn3vh+CvXz//CgUIqPhNp3sIJbYJdqPrpMg5EMBd+I6CmPIzJzOF6NbDxzBtnf3Yu3f47X0XNBFyjuABAuPwU4D0pRBBawosrLwsVPtLU//rGXQ99/U9T3UVfwR8k7qmfnavk+iveqpQwdwZCzklzmRbQMARIzVHTolyV4rVIYVcg1K/frdQNdWz8+dhFGV99/Kl8NWhqZLK2DFysViJ9vWReVjMBGIBBgau4xmXtFMnogAwadqWLfcU961eOIEGCBAkSJEiQIEGCBAkSJEgwVfg3+LzfuLeHV2MAAAAASUVORK5CYII=)}div.feedback{position:absolute;bottom:3px;left:0;right:3px;padding:0 10px 3px;z-index:1000;border:1px solid #888;border-radius:5px;background-color:#cff;box-shadow:3px 3px 5px #888}div.feedback.warning{background-color:#fdd}.modal-header .glyphicon-warning-sign{color:#fa0;font-size:150%}.modal-header .warning{color:red}div.btn-group.diff{margin-top:1em}div.btn-transparent button.dropdown-toggle{background:none repeat scroll 0 0 transparent;border:0 none;cursor:pointer;padding:0;color:#000;float:right;font-size:16px;font-weight:700;line-height:1;opacity:.2}div.btn-transparent>button:hover{opacity:.8}#login.login>.logout{display:none}#login.logout>.login{display:none}#login.logout>.logout{color:green}#login .value{margin-left:5px}iframe.login{width:90%;margin:0 auto;display:block;height:30ex}button.login-cont{margin:2ex auto 2ex;display:block}img.login-with,img.profile-picture{width:24px;height:24px}div.user-menu.btn-transparent button.dropdown-toggle{opacity:1}div.notification{display:inline-block;position:absolute;min-width:10em;background:#cff;padding:5px 1em;display:none;z-index:1000}a.dropdown-toggle.avatar{padding:0;margin-left:2px}img.avatar{width:24px;margin-top:4px;margin-bottom:4px}img.avatar:hover{width:32px;margin-top:0;margin-bottom:0}div.user-count{clear:both;text-align:center;color:#888;font-style:italic;font-size:75%;display:none}li.myself{border-bottom:3px solid green}li.user.lost{opacity:.2}.notify-arrow{background:#cff;border:1px solid #888;border-radius:5px;box-shadow:6px 6px 3px #aaa}.notify-arrow:after,.notify-arrow:before{bottom:100%;right:12px;border:solid transparent;content:" ";height:0;width:0;position:absolute}.notify-arrow:after{border-color:rgba(192,255,255,0);border-bottom-color:#cff;border-width:14px;margin-left:-14px}.notify-arrow:before{border-color:rgba(128,128,128,0);border-bottom-color:#888;border-width:15px;margin-left:-15px}div.chatroom{width:100%;height:100%;position:relative;overflow:hidden}div.chatroom span.glyphicon.menu{position:absolute;font-size:1.5em;top:5px;right:5px;opacity:.2}div.chatroom span.glyphicon.menu:hover{opacity:.8}div.chat-conversation{width:100%;height:calc(100% - 2.5em);overflow:auto;padding:5px}div.chat-input{border-top:1px solid #888;box-sizing:border-box;width:100%;height:2.5em}table.chat-input{width:100%;height:100%}td.chat-send{text-align:right;white-space:nowrap;vertical-align:middle;padding:5px}td.chat-send>div{display:flex}td.chat-text{width:100%;padding:0 5px}table.chat-input textarea{resize:none;box-sizing:border-box;width:100%;height:2.5em;border:0}div.chatroom div.chat-message{position:relative;font-size:90%;margin-right:10%;margin-bottom:1ex;background-color:#eee;border:1px solid #ccc;border-radius:5px;padding:3px 5px}div.chatroom div.chat-message.self{margin-right:0;margin-left:10%}div.chat-message img.avatar{position:absolute;margin-top:0;top:0;right:0;border-radius:5px;width:24px}span.chat-sender{font-weight:700;color:#4888be}span.chat-time{font-family:italic;color:#4888be}span.chat-sender::after{content:": "}span.commit-message{color:#060}span.no-commit-message{font-size:80%;color:#f80}.chat-message .tooltip{z-index:5000;position:fixed}.chat-message .tooltip-inner{background:#ffd;padding:5px 5px;border:1px solid #888;border-radius:5px}.chat-message .tooltip-inner pre.cm-s-prolog{padding:0 5px;background:0 0;border:0;margin:0}.flash{animation:flash 2s ease-out 1;-webkit-animation:flash 2s ease-out 1}@-webkit-keyframes flash{from{background-color:#ffa}to{background-color:#fff}}@keyframes flash{from{background-color:#ffa}to{background-color:#fff}}a.pengine-logo{position:absolute;top:4px;left:4px;width:42px;height:42px;background-image:url(../icons/logo.png);background-size:100%}.splitter_panel .hsplitter,.splitter_panel .vsplitter{z-index:100;border:2px outset #ccc}.splitter_panel .vsplitter{width:3px}.splitter_panel .hsplitter{height:3px}.splitter_panel .bottom_panel,.splitter_panel .hsplitter,.splitter_panel .left_panel,.splitter_panel .right_panel,.splitter_panel .top_panel,.splitter_panel .vsplitter{overflow:visible}body .modal-dialog{width:80%;max-width:800px;margin-left:auto;margin-right:auto}body .modal-dialog.modal-wide{width:90%;max-width:none}body .modal-dialog.swish-embedded-manual{width:90%;max-width:1000px}body .modal-dialog.swish-embedded-manual div.modal-body{padding:0}iframe.swish-embedded-manual{width:100%;border:0}
\ No newline at end of file
diff --git a/web/css/swish-min.css.gz b/web/css/swish-min.css.gz
index 16230b5..1e7997e 100644
Binary files a/web/css/swish-min.css.gz and b/web/css/swish-min.css.gz differ
diff --git a/web/help/about.html b/web/help/about.html
index 98a4fb5..db181df 100644
--- a/web/help/about.html
+++ b/web/help/about.html
@@ -65,7 +65,13 @@ style="color:maroon">SH</span> source is available from <a
 href="http://github.com/SWI-Prolog/swish.git">Github</a>. It is under
 heavy development and often requires SWI-Prolog 7 installed from the
 latest <a href="http://github.com/SWI-Prolog/swipl-devel.git">GIT</a>.
+</p>
+
 <p>
+Avatar graphics created by <a href="http://www.noblemaster.com">Noble
+Master Games</a>, designed by
+<a href="http://liea.deviantart.com">Mei-Li Nieuwland</a>.
+</p>
 
 <div class="github">
 <iframe class="github-btn" src="http://ghbtns.com/github-btn.html?user=SWI-Prolog&amp;repo=swish&amp;type=watch&amp;count=true" width="100" height="20" title="Star on GitHub"></iframe>
diff --git a/web/help/chat.html b/web/help/chat.html
new file mode 100644
index 0000000..265967f
--- /dev/null
+++ b/web/help/chat.html
@@ -0,0 +1,93 @@
+<!DOCTYPE HTML>
+
+<html>
+  <head>
+  <title>SWISH chat service</title>
+  </head>
+  <body>
+
+<div class="dropup">
+<p>
+The <span style="color:darkblue">SWI</span><span
+style="color:maroon">SH</span> chat services allows you to chat with
+users about a file. <span style="color:darkblue">SWI</span><span
+style="color:maroon">SH</span> displays an <i>avatar</i> for each user
+with whom you share an open file. If you select <b>File/Chat ...</b> the
+current notebook or program gets a chat window displayed below it,
+preloaded with older chat messages about this file.  A chat message
+may include one or more <b>payload</b> objects that are made visible
+as buttons.  Most payloads are added using the <a class="btn
+btn-xs btn-primary">Send <b class="caret"></b></a> button menu.  Defined
+payloads are:
+</p>
+
+  <ul>
+    <li>The <b>selection</b>.  If you have made a selection on the
+        page, this is sent along with the chat message.  Clicking
+        on the <a class="btn btn-xs btn-primary"><span
+	class="glyphicon glyphicon-eye-open"></span></a> button restores
+	this selection.  Note that you can make <b>multiple selections</b>
+	using <b>Control-click</b> in the CodeMirror editor.
+    <li>Your current <b>query</b> can be included using the <a class="btn
+        btn-xs btn-primary">Send <b class="caret"></b></a>.
+    <li>System generated <b>update messages</b> include a payload that
+        allows you to open the file in <b>before/after</b> mode as well
+	as examine the <b>differences</b>
+  </ul>
+
+<p>
+Finally, the <a class="btn btn-xs btn-primary">Send <b class="caret"></b></a>
+button may be used to create a link from the <b>shared chatroom</b> to this
+file to <b>ask for support</b>.
+</p>
+
+
+<h3 id="chat-help">The shared chat room</h3>
+
+<p class="dropup">
+The notebook <a href="/p/Help.swinb">Help.swinb</a> provides a place to
+find buddies. It can be opened from <b>File/Chat help room ...</b> and
+messages may be cross-posted to this shared space using <b>Broadcast to
+help room</b> from the <a class="btn btn-xs btn-primary">Send <b
+class="caret"></b></a> button. The message that appears in the shared
+room contains a link to the file from which it was created.
+<p>
+
+<h3 id="chat-markdown">Markdown in chat messages</h3>
+
+<p>
+Chat messages are subject to a limited form of Markdown processing.
+Currently, the patterns below replaced.  Note that these are simplied
+forms of the actual regular expressions which use stronger boundary
+conditions.
+</p>
+
+<table class="table table-condensed" style="width:80%; margin:auto">
+<tr><th>Pattern<th>Example<th>Meaning
+<tr><td>\b\w+.pl<td>program.pl<td>Link to Prolog program
+<tr><td>\b\w+.swinb<td>notebook.swinb<td>Link to SWISH notebook
+<tr><td>\w+/\d<td>between/3<td>Link to documentation on predicate
+<tr><td>`[^`]+`<td>`A is 1+1`<td><code>A is 1+1</code>
+<tr><td>*[^*]+*<td>*never*<td><b>never</b>
+<tr><td>__[^_]+__<td>__always__<td><b>always</b>
+<tr><td>_[^_]+_<td>_italic_<td><i>italic</i>
+</table>
+
+
+<h3 id="chat-status">Status of the SWISH sharing service</h3>
+
+<p>
+What you are seeing are the first steps to allow users of SWISH to communicate.
+There are many facilities we have in mind, such as:
+</p>
+
+<ul>
+  <li>Connect editors for collaborative editing
+  <li>Make <i>teams</i> that connect people also if they are not editing
+      the same file.
+  <li>Allow Prolog programs to exchange messages through the chat room.
+</ul>
+</div>
+
+</body>
+</html>
diff --git a/web/help/help.html b/web/help/help.html
index a3d7bfc..9bc2de1 100644
--- a/web/help/help.html
+++ b/web/help/help.html
@@ -113,6 +113,7 @@ program using Prolog's <b>include/1</b> predicate as illustrated below.
 :- include(clever).
 </pre>
 
+<p>
 You can also include a <em>specific version</em> of a program by including
 its <em>hash</em>.  You can find the hash of a specific version using
 <b>Info &amp; History ...</b>, selecting the desired version and opening
@@ -123,6 +124,16 @@ browser's address field.  Now, include this version using e.g.,
 :- include('23dacada6952ec6701da2dc9d4ebcf5c7b860380').
 </pre>
 
+<p>
+You can also use the <i>Alias(Name)</i> syntax to include files from
+the directories in the search path <i>Alias</i>.  By default this is
+enabled for <code>example</code>, so the following directive allow you
+to reuse the predicates from the <em>movies</em> example:
+
+<pre style="font-size:80%">
+:- include(example(movies)).
+</pre>
+
 <p>
 Using <b>File/Collaborate ...</b>, you create a
 <a target="_blank" href="https://togetherjs.com/">TogetherJS</a> session
diff --git a/web/help/login.html b/web/help/login.html
new file mode 100644
index 0000000..d16766a
--- /dev/null
+++ b/web/help/login.html
@@ -0,0 +1,48 @@
+<!DOCTYPE HTML>
+
+<html>
+  <head>
+  <title>Login functions</title>
+  </head>
+  <body>
+
+<p>
+Depending on the configuration of <span
+style="color:darkblue">SWI</span><span style="color:maroon">SH</span>,
+the user may be able to login using either local login or federated
+login from e.g., Google or Stackexchange (e.g., Stackoverflow).  Login
+gives some additional features:
+</p>
+
+<ul>
+  <li>
+<p>
+A <b>stable identifier</b> associated an <i>avatar</i> of choice and
+email address flags documents and chat messages unambiguously to you,
+regardless of the device you use.
+  <li>
+<p>
+<b>Follow document</b>, available from the <b>File</b> menu allows
+you to receive email and notification messages about actions on files.
+Selecting <b>update</b> causes notifications if a new version of the document
+is saved or the file is <i>forked</i> (saved under a different name).
+Selecting <b>chat</b> causes notification if someone chats about the document.
+</p>
+
+<p>
+The <b>Save</b> dialog contains	a checkbox that allows you to follow files
+to which you have made changes.  This checkbox is by default enabled.
+</p>
+
+  <li>
+<p>
+Using the <b>Save</b> dialog you may <b>Protect your document</b> by limiting
+who may save new versions.  Values are <i>any</i> (anyone, logged in or not
+may save a new version), <i>login</i> (only people that are logged in may
+save a new version) or <i>owner</i> (only you can save a new version).
+</p>
+</ul>
+
+
+</body>
+</html>
diff --git a/web/help/notebook.html b/web/help/notebook.html
index ad0c627..02f2356 100644
--- a/web/help/notebook.html
+++ b/web/help/notebook.html
@@ -11,7 +11,7 @@ p.note span.glyphicon-hand-right {
 float: left; font-size: 120%; color: orange; padding-right: 0.2em;
 }
 
-a.nb-cell.program { margin: 0px; }
+a.nb-no-cell.program { margin: 0px; }
 </style>
 <p>
 A notebook is a list of <i>cells</i>. Notebooks are different from a
@@ -62,9 +62,9 @@ markdown notation <code>[label](myfile.pl)</code>, e.g.,
 <p>
 A notebook <em>query</em> cell is executed against the program cell
 <strong>above it</strong> and all program cells marked as
-<em>background</em> using the <a class="nb-cell btn-default program
+<em>background</em> using the <a class="nb-no-cell btn-default program
 background btn btn-image btn-xs"><span
-class="image-icon"></span></a> button. Click the <a class="nb-cell
+class="image-icon"></span></a> button. Click the <a class="nb-no-cell
 btn-default program btn btn-image btn-xs"><span
 class="image-icon"></span></a> button to turn a normal program cell
 into a <i>background</i> cell.
diff --git a/web/icons/noble/components/avatar_accessory_1.png b/web/icons/noble/components/avatar_accessory_1.png
new file mode 100644
index 0000000..4f04f2e
Binary files /dev/null and b/web/icons/noble/components/avatar_accessory_1.png differ
diff --git a/web/icons/noble/components/avatar_accessory_10.png b/web/icons/noble/components/avatar_accessory_10.png
new file mode 100644
index 0000000..94cfa37
Binary files /dev/null and b/web/icons/noble/components/avatar_accessory_10.png differ
diff --git a/web/icons/noble/components/avatar_accessory_11.png b/web/icons/noble/components/avatar_accessory_11.png
new file mode 100644
index 0000000..aef9f1e
Binary files /dev/null and b/web/icons/noble/components/avatar_accessory_11.png differ
diff --git a/web/icons/noble/components/avatar_accessory_12.png b/web/icons/noble/components/avatar_accessory_12.png
new file mode 100644
index 0000000..655b16d
Binary files /dev/null and b/web/icons/noble/components/avatar_accessory_12.png differ
diff --git a/web/icons/noble/components/avatar_accessory_13.png b/web/icons/noble/components/avatar_accessory_13.png
new file mode 100644
index 0000000..90e93b9
Binary files /dev/null and b/web/icons/noble/components/avatar_accessory_13.png differ
diff --git a/web/icons/noble/components/avatar_accessory_14.png b/web/icons/noble/components/avatar_accessory_14.png
new file mode 100644
index 0000000..d62eb1a
Binary files /dev/null and b/web/icons/noble/components/avatar_accessory_14.png differ
diff --git a/web/icons/noble/components/avatar_accessory_15.png b/web/icons/noble/components/avatar_accessory_15.png
new file mode 100644
index 0000000..83cedbd
Binary files /dev/null and b/web/icons/noble/components/avatar_accessory_15.png differ
diff --git a/web/icons/noble/components/avatar_accessory_16.png b/web/icons/noble/components/avatar_accessory_16.png
new file mode 100644
index 0000000..686b430
Binary files /dev/null and b/web/icons/noble/components/avatar_accessory_16.png differ
diff --git a/web/icons/noble/components/avatar_accessory_17.png b/web/icons/noble/components/avatar_accessory_17.png
new file mode 100644
index 0000000..4a9fe32
Binary files /dev/null and b/web/icons/noble/components/avatar_accessory_17.png differ
diff --git a/web/icons/noble/components/avatar_accessory_18.png b/web/icons/noble/components/avatar_accessory_18.png
new file mode 100644
index 0000000..34fce88
Binary files /dev/null and b/web/icons/noble/components/avatar_accessory_18.png differ
diff --git a/web/icons/noble/components/avatar_accessory_19.png b/web/icons/noble/components/avatar_accessory_19.png
new file mode 100644
index 0000000..b54b927
Binary files /dev/null and b/web/icons/noble/components/avatar_accessory_19.png differ
diff --git a/web/icons/noble/components/avatar_accessory_2.png b/web/icons/noble/components/avatar_accessory_2.png
new file mode 100644
index 0000000..284250f
Binary files /dev/null and b/web/icons/noble/components/avatar_accessory_2.png differ
diff --git a/web/icons/noble/components/avatar_accessory_20.png b/web/icons/noble/components/avatar_accessory_20.png
new file mode 100644
index 0000000..e8484f4
Binary files /dev/null and b/web/icons/noble/components/avatar_accessory_20.png differ
diff --git a/web/icons/noble/components/avatar_accessory_3.png b/web/icons/noble/components/avatar_accessory_3.png
new file mode 100644
index 0000000..a281126
Binary files /dev/null and b/web/icons/noble/components/avatar_accessory_3.png differ
diff --git a/web/icons/noble/components/avatar_accessory_4.png b/web/icons/noble/components/avatar_accessory_4.png
new file mode 100644
index 0000000..9172577
Binary files /dev/null and b/web/icons/noble/components/avatar_accessory_4.png differ
diff --git a/web/icons/noble/components/avatar_accessory_5.png b/web/icons/noble/components/avatar_accessory_5.png
new file mode 100644
index 0000000..7b04564
Binary files /dev/null and b/web/icons/noble/components/avatar_accessory_5.png differ
diff --git a/web/icons/noble/components/avatar_accessory_6.png b/web/icons/noble/components/avatar_accessory_6.png
new file mode 100644
index 0000000..113cb3e
Binary files /dev/null and b/web/icons/noble/components/avatar_accessory_6.png differ
diff --git a/web/icons/noble/components/avatar_accessory_7.png b/web/icons/noble/components/avatar_accessory_7.png
new file mode 100644
index 0000000..c0eb475
Binary files /dev/null and b/web/icons/noble/components/avatar_accessory_7.png differ
diff --git a/web/icons/noble/components/avatar_accessory_8.png b/web/icons/noble/components/avatar_accessory_8.png
new file mode 100644
index 0000000..794f5d5
Binary files /dev/null and b/web/icons/noble/components/avatar_accessory_8.png differ
diff --git a/web/icons/noble/components/avatar_accessory_9.png b/web/icons/noble/components/avatar_accessory_9.png
new file mode 100644
index 0000000..aba8479
Binary files /dev/null and b/web/icons/noble/components/avatar_accessory_9.png differ
diff --git a/web/icons/noble/components/avatar_accessory_f21.png b/web/icons/noble/components/avatar_accessory_f21.png
new file mode 100644
index 0000000..78247fc
Binary files /dev/null and b/web/icons/noble/components/avatar_accessory_f21.png differ
diff --git a/web/icons/noble/components/avatar_accessory_m21.png b/web/icons/noble/components/avatar_accessory_m21.png
new file mode 100644
index 0000000..1b3884b
Binary files /dev/null and b/web/icons/noble/components/avatar_accessory_m21.png differ
diff --git a/web/icons/noble/components/avatar_beard_1.png b/web/icons/noble/components/avatar_beard_1.png
new file mode 100644
index 0000000..f8be77e
Binary files /dev/null and b/web/icons/noble/components/avatar_beard_1.png differ
diff --git a/web/icons/noble/components/avatar_beard_2.png b/web/icons/noble/components/avatar_beard_2.png
new file mode 100644
index 0000000..1a07795
Binary files /dev/null and b/web/icons/noble/components/avatar_beard_2.png differ
diff --git a/web/icons/noble/components/avatar_beard_3.png b/web/icons/noble/components/avatar_beard_3.png
new file mode 100644
index 0000000..9bae715
Binary files /dev/null and b/web/icons/noble/components/avatar_beard_3.png differ
diff --git a/web/icons/noble/components/avatar_beard_4.png b/web/icons/noble/components/avatar_beard_4.png
new file mode 100644
index 0000000..fe18590
Binary files /dev/null and b/web/icons/noble/components/avatar_beard_4.png differ
diff --git a/web/icons/noble/components/avatar_beard_5.png b/web/icons/noble/components/avatar_beard_5.png
new file mode 100644
index 0000000..6e287fb
Binary files /dev/null and b/web/icons/noble/components/avatar_beard_5.png differ
diff --git a/web/icons/noble/components/avatar_boa_1.png b/web/icons/noble/components/avatar_boa_1.png
new file mode 100644
index 0000000..1ee9065
Binary files /dev/null and b/web/icons/noble/components/avatar_boa_1.png differ
diff --git a/web/icons/noble/components/avatar_boa_2.png b/web/icons/noble/components/avatar_boa_2.png
new file mode 100644
index 0000000..2a1e0c3
Binary files /dev/null and b/web/icons/noble/components/avatar_boa_2.png differ
diff --git a/web/icons/noble/components/avatar_boa_3.png b/web/icons/noble/components/avatar_boa_3.png
new file mode 100644
index 0000000..60ab546
Binary files /dev/null and b/web/icons/noble/components/avatar_boa_3.png differ
diff --git a/web/icons/noble/components/avatar_boa_4.png b/web/icons/noble/components/avatar_boa_4.png
new file mode 100644
index 0000000..32a30e4
Binary files /dev/null and b/web/icons/noble/components/avatar_boa_4.png differ
diff --git a/web/icons/noble/components/avatar_disabled.png b/web/icons/noble/components/avatar_disabled.png
new file mode 100644
index 0000000..c1aafc3
Binary files /dev/null and b/web/icons/noble/components/avatar_disabled.png differ
diff --git a/web/icons/noble/components/avatar_eye_f1.png b/web/icons/noble/components/avatar_eye_f1.png
new file mode 100644
index 0000000..6d2cedd
Binary files /dev/null and b/web/icons/noble/components/avatar_eye_f1.png differ
diff --git a/web/icons/noble/components/avatar_eye_f2.png b/web/icons/noble/components/avatar_eye_f2.png
new file mode 100644
index 0000000..6c057cd
Binary files /dev/null and b/web/icons/noble/components/avatar_eye_f2.png differ
diff --git a/web/icons/noble/components/avatar_eye_f3.png b/web/icons/noble/components/avatar_eye_f3.png
new file mode 100644
index 0000000..7814fa5
Binary files /dev/null and b/web/icons/noble/components/avatar_eye_f3.png differ
diff --git a/web/icons/noble/components/avatar_eye_f4.png b/web/icons/noble/components/avatar_eye_f4.png
new file mode 100644
index 0000000..d137695
Binary files /dev/null and b/web/icons/noble/components/avatar_eye_f4.png differ
diff --git a/web/icons/noble/components/avatar_eye_f5.png b/web/icons/noble/components/avatar_eye_f5.png
new file mode 100644
index 0000000..ee86885
Binary files /dev/null and b/web/icons/noble/components/avatar_eye_f5.png differ
diff --git a/web/icons/noble/components/avatar_eye_f6.png b/web/icons/noble/components/avatar_eye_f6.png
new file mode 100644
index 0000000..ad958f8
Binary files /dev/null and b/web/icons/noble/components/avatar_eye_f6.png differ
diff --git a/web/icons/noble/components/avatar_eye_f7.png b/web/icons/noble/components/avatar_eye_f7.png
new file mode 100644
index 0000000..350e811
Binary files /dev/null and b/web/icons/noble/components/avatar_eye_f7.png differ
diff --git a/web/icons/noble/components/avatar_eye_f8.png b/web/icons/noble/components/avatar_eye_f8.png
new file mode 100644
index 0000000..27b02f0
Binary files /dev/null and b/web/icons/noble/components/avatar_eye_f8.png differ
diff --git a/web/icons/noble/components/avatar_eye_m1.png b/web/icons/noble/components/avatar_eye_m1.png
new file mode 100644
index 0000000..15daaaa
Binary files /dev/null and b/web/icons/noble/components/avatar_eye_m1.png differ
diff --git a/web/icons/noble/components/avatar_eye_m2.png b/web/icons/noble/components/avatar_eye_m2.png
new file mode 100644
index 0000000..c012bdc
Binary files /dev/null and b/web/icons/noble/components/avatar_eye_m2.png differ
diff --git a/web/icons/noble/components/avatar_eye_m3.png b/web/icons/noble/components/avatar_eye_m3.png
new file mode 100644
index 0000000..00a3a26
Binary files /dev/null and b/web/icons/noble/components/avatar_eye_m3.png differ
diff --git a/web/icons/noble/components/avatar_eye_m4.png b/web/icons/noble/components/avatar_eye_m4.png
new file mode 100644
index 0000000..fe52be9
Binary files /dev/null and b/web/icons/noble/components/avatar_eye_m4.png differ
diff --git a/web/icons/noble/components/avatar_eye_m5.png b/web/icons/noble/components/avatar_eye_m5.png
new file mode 100644
index 0000000..cae3853
Binary files /dev/null and b/web/icons/noble/components/avatar_eye_m5.png differ
diff --git a/web/icons/noble/components/avatar_eye_m6.png b/web/icons/noble/components/avatar_eye_m6.png
new file mode 100644
index 0000000..bb50ca6
Binary files /dev/null and b/web/icons/noble/components/avatar_eye_m6.png differ
diff --git a/web/icons/noble/components/avatar_eye_m7.png b/web/icons/noble/components/avatar_eye_m7.png
new file mode 100644
index 0000000..45a24e8
Binary files /dev/null and b/web/icons/noble/components/avatar_eye_m7.png differ
diff --git a/web/icons/noble/components/avatar_eye_m8.png b/web/icons/noble/components/avatar_eye_m8.png
new file mode 100644
index 0000000..b872d18
Binary files /dev/null and b/web/icons/noble/components/avatar_eye_m8.png differ
diff --git a/web/icons/noble/components/avatar_eyepatch_1.png b/web/icons/noble/components/avatar_eyepatch_1.png
new file mode 100644
index 0000000..25358fc
Binary files /dev/null and b/web/icons/noble/components/avatar_eyepatch_1.png differ
diff --git a/web/icons/noble/components/avatar_eyepatch_2.png b/web/icons/noble/components/avatar_eyepatch_2.png
new file mode 100644
index 0000000..b1a7681
Binary files /dev/null and b/web/icons/noble/components/avatar_eyepatch_2.png differ
diff --git a/web/icons/noble/components/avatar_glasses_1.png b/web/icons/noble/components/avatar_glasses_1.png
new file mode 100644
index 0000000..637c388
Binary files /dev/null and b/web/icons/noble/components/avatar_glasses_1.png differ
diff --git a/web/icons/noble/components/avatar_glasses_2.png b/web/icons/noble/components/avatar_glasses_2.png
new file mode 100644
index 0000000..83f42a5
Binary files /dev/null and b/web/icons/noble/components/avatar_glasses_2.png differ
diff --git a/web/icons/noble/components/avatar_glasses_3.png b/web/icons/noble/components/avatar_glasses_3.png
new file mode 100644
index 0000000..942f6eb
Binary files /dev/null and b/web/icons/noble/components/avatar_glasses_3.png differ
diff --git a/web/icons/noble/components/avatar_glasses_4.png b/web/icons/noble/components/avatar_glasses_4.png
new file mode 100644
index 0000000..bbe6fd1
Binary files /dev/null and b/web/icons/noble/components/avatar_glasses_4.png differ
diff --git a/web/icons/noble/components/avatar_hair_f1.png b/web/icons/noble/components/avatar_hair_f1.png
new file mode 100644
index 0000000..69f0e05
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_f1.png differ
diff --git a/web/icons/noble/components/avatar_hair_f10.png b/web/icons/noble/components/avatar_hair_f10.png
new file mode 100644
index 0000000..9a6ed47
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_f10.png differ
diff --git a/web/icons/noble/components/avatar_hair_f11.png b/web/icons/noble/components/avatar_hair_f11.png
new file mode 100644
index 0000000..776655f
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_f11.png differ
diff --git a/web/icons/noble/components/avatar_hair_f12.png b/web/icons/noble/components/avatar_hair_f12.png
new file mode 100644
index 0000000..5c969cc
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_f12.png differ
diff --git a/web/icons/noble/components/avatar_hair_f13.png b/web/icons/noble/components/avatar_hair_f13.png
new file mode 100644
index 0000000..f712229
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_f13.png differ
diff --git a/web/icons/noble/components/avatar_hair_f14.png b/web/icons/noble/components/avatar_hair_f14.png
new file mode 100644
index 0000000..9f90944
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_f14.png differ
diff --git a/web/icons/noble/components/avatar_hair_f15.png b/web/icons/noble/components/avatar_hair_f15.png
new file mode 100644
index 0000000..38fd6a0
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_f15.png differ
diff --git a/web/icons/noble/components/avatar_hair_f16.png b/web/icons/noble/components/avatar_hair_f16.png
new file mode 100644
index 0000000..3fd3b00
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_f16.png differ
diff --git a/web/icons/noble/components/avatar_hair_f17.png b/web/icons/noble/components/avatar_hair_f17.png
new file mode 100644
index 0000000..b5e0f73
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_f17.png differ
diff --git a/web/icons/noble/components/avatar_hair_f18.png b/web/icons/noble/components/avatar_hair_f18.png
new file mode 100644
index 0000000..36a1516
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_f18.png differ
diff --git a/web/icons/noble/components/avatar_hair_f19.png b/web/icons/noble/components/avatar_hair_f19.png
new file mode 100644
index 0000000..332910e
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_f19.png differ
diff --git a/web/icons/noble/components/avatar_hair_f2.png b/web/icons/noble/components/avatar_hair_f2.png
new file mode 100644
index 0000000..4e37545
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_f2.png differ
diff --git a/web/icons/noble/components/avatar_hair_f20.png b/web/icons/noble/components/avatar_hair_f20.png
new file mode 100644
index 0000000..4072d2c
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_f20.png differ
diff --git a/web/icons/noble/components/avatar_hair_f21.png b/web/icons/noble/components/avatar_hair_f21.png
new file mode 100644
index 0000000..04c85d9
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_f21.png differ
diff --git a/web/icons/noble/components/avatar_hair_f22.png b/web/icons/noble/components/avatar_hair_f22.png
new file mode 100644
index 0000000..d35e100
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_f22.png differ
diff --git a/web/icons/noble/components/avatar_hair_f23.png b/web/icons/noble/components/avatar_hair_f23.png
new file mode 100644
index 0000000..b202f5f
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_f23.png differ
diff --git a/web/icons/noble/components/avatar_hair_f24.png b/web/icons/noble/components/avatar_hair_f24.png
new file mode 100644
index 0000000..9e08ae1
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_f24.png differ
diff --git a/web/icons/noble/components/avatar_hair_f25.png b/web/icons/noble/components/avatar_hair_f25.png
new file mode 100644
index 0000000..7c90a46
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_f25.png differ
diff --git a/web/icons/noble/components/avatar_hair_f26.png b/web/icons/noble/components/avatar_hair_f26.png
new file mode 100644
index 0000000..f329af7
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_f26.png differ
diff --git a/web/icons/noble/components/avatar_hair_f3.png b/web/icons/noble/components/avatar_hair_f3.png
new file mode 100644
index 0000000..ad87faf
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_f3.png differ
diff --git a/web/icons/noble/components/avatar_hair_f4.png b/web/icons/noble/components/avatar_hair_f4.png
new file mode 100644
index 0000000..94502e0
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_f4.png differ
diff --git a/web/icons/noble/components/avatar_hair_f5.png b/web/icons/noble/components/avatar_hair_f5.png
new file mode 100644
index 0000000..0dc68c0
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_f5.png differ
diff --git a/web/icons/noble/components/avatar_hair_f6.png b/web/icons/noble/components/avatar_hair_f6.png
new file mode 100644
index 0000000..142e7aa
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_f6.png differ
diff --git a/web/icons/noble/components/avatar_hair_f7.png b/web/icons/noble/components/avatar_hair_f7.png
new file mode 100644
index 0000000..c81df40
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_f7.png differ
diff --git a/web/icons/noble/components/avatar_hair_f8.png b/web/icons/noble/components/avatar_hair_f8.png
new file mode 100644
index 0000000..8ec6b01
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_f8.png differ
diff --git a/web/icons/noble/components/avatar_hair_f9.png b/web/icons/noble/components/avatar_hair_f9.png
new file mode 100644
index 0000000..dbd2c3a
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_f9.png differ
diff --git a/web/icons/noble/components/avatar_hair_m1.png b/web/icons/noble/components/avatar_hair_m1.png
new file mode 100644
index 0000000..aabadc9
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_m1.png differ
diff --git a/web/icons/noble/components/avatar_hair_m10.png b/web/icons/noble/components/avatar_hair_m10.png
new file mode 100644
index 0000000..0ccbac1
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_m10.png differ
diff --git a/web/icons/noble/components/avatar_hair_m11.png b/web/icons/noble/components/avatar_hair_m11.png
new file mode 100644
index 0000000..aa8023a
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_m11.png differ
diff --git a/web/icons/noble/components/avatar_hair_m12.png b/web/icons/noble/components/avatar_hair_m12.png
new file mode 100644
index 0000000..d2717ed
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_m12.png differ
diff --git a/web/icons/noble/components/avatar_hair_m13.png b/web/icons/noble/components/avatar_hair_m13.png
new file mode 100644
index 0000000..43f68a3
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_m13.png differ
diff --git a/web/icons/noble/components/avatar_hair_m14.png b/web/icons/noble/components/avatar_hair_m14.png
new file mode 100644
index 0000000..7281ded
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_m14.png differ
diff --git a/web/icons/noble/components/avatar_hair_m15.png b/web/icons/noble/components/avatar_hair_m15.png
new file mode 100644
index 0000000..c5fb096
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_m15.png differ
diff --git a/web/icons/noble/components/avatar_hair_m16.png b/web/icons/noble/components/avatar_hair_m16.png
new file mode 100644
index 0000000..1b0dc52
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_m16.png differ
diff --git a/web/icons/noble/components/avatar_hair_m17.png b/web/icons/noble/components/avatar_hair_m17.png
new file mode 100644
index 0000000..f3d187c
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_m17.png differ
diff --git a/web/icons/noble/components/avatar_hair_m18.png b/web/icons/noble/components/avatar_hair_m18.png
new file mode 100644
index 0000000..4b7c380
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_m18.png differ
diff --git a/web/icons/noble/components/avatar_hair_m19.png b/web/icons/noble/components/avatar_hair_m19.png
new file mode 100644
index 0000000..55aa024
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_m19.png differ
diff --git a/web/icons/noble/components/avatar_hair_m2.png b/web/icons/noble/components/avatar_hair_m2.png
new file mode 100644
index 0000000..ae22a68
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_m2.png differ
diff --git a/web/icons/noble/components/avatar_hair_m20.png b/web/icons/noble/components/avatar_hair_m20.png
new file mode 100644
index 0000000..5a0ccd0
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_m20.png differ
diff --git a/web/icons/noble/components/avatar_hair_m21.png b/web/icons/noble/components/avatar_hair_m21.png
new file mode 100644
index 0000000..c20852c
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_m21.png differ
diff --git a/web/icons/noble/components/avatar_hair_m22.png b/web/icons/noble/components/avatar_hair_m22.png
new file mode 100644
index 0000000..7437266
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_m22.png differ
diff --git a/web/icons/noble/components/avatar_hair_m23.png b/web/icons/noble/components/avatar_hair_m23.png
new file mode 100644
index 0000000..1bd1ccd
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_m23.png differ
diff --git a/web/icons/noble/components/avatar_hair_m24.png b/web/icons/noble/components/avatar_hair_m24.png
new file mode 100644
index 0000000..75e8de0
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_m24.png differ
diff --git a/web/icons/noble/components/avatar_hair_m25.png b/web/icons/noble/components/avatar_hair_m25.png
new file mode 100644
index 0000000..30073b5
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_m25.png differ
diff --git a/web/icons/noble/components/avatar_hair_m26.png b/web/icons/noble/components/avatar_hair_m26.png
new file mode 100644
index 0000000..5f285d2
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_m26.png differ
diff --git a/web/icons/noble/components/avatar_hair_m3.png b/web/icons/noble/components/avatar_hair_m3.png
new file mode 100644
index 0000000..04f956b
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_m3.png differ
diff --git a/web/icons/noble/components/avatar_hair_m4.png b/web/icons/noble/components/avatar_hair_m4.png
new file mode 100644
index 0000000..cbdff57
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_m4.png differ
diff --git a/web/icons/noble/components/avatar_hair_m5.png b/web/icons/noble/components/avatar_hair_m5.png
new file mode 100644
index 0000000..42ad5e5
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_m5.png differ
diff --git a/web/icons/noble/components/avatar_hair_m6.png b/web/icons/noble/components/avatar_hair_m6.png
new file mode 100644
index 0000000..fa1e825
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_m6.png differ
diff --git a/web/icons/noble/components/avatar_hair_m7.png b/web/icons/noble/components/avatar_hair_m7.png
new file mode 100644
index 0000000..796c5ce
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_m7.png differ
diff --git a/web/icons/noble/components/avatar_hair_m8.png b/web/icons/noble/components/avatar_hair_m8.png
new file mode 100644
index 0000000..dd77fe1
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_m8.png differ
diff --git a/web/icons/noble/components/avatar_hair_m9.png b/web/icons/noble/components/avatar_hair_m9.png
new file mode 100644
index 0000000..d842f22
Binary files /dev/null and b/web/icons/noble/components/avatar_hair_m9.png differ
diff --git a/web/icons/noble/components/avatar_head_f1.png b/web/icons/noble/components/avatar_head_f1.png
new file mode 100644
index 0000000..57bb01a
Binary files /dev/null and b/web/icons/noble/components/avatar_head_f1.png differ
diff --git a/web/icons/noble/components/avatar_head_f10.png b/web/icons/noble/components/avatar_head_f10.png
new file mode 100644
index 0000000..7a0784e
Binary files /dev/null and b/web/icons/noble/components/avatar_head_f10.png differ
diff --git a/web/icons/noble/components/avatar_head_f11.png b/web/icons/noble/components/avatar_head_f11.png
new file mode 100644
index 0000000..9b7c369
Binary files /dev/null and b/web/icons/noble/components/avatar_head_f11.png differ
diff --git a/web/icons/noble/components/avatar_head_f12.png b/web/icons/noble/components/avatar_head_f12.png
new file mode 100644
index 0000000..828a850
Binary files /dev/null and b/web/icons/noble/components/avatar_head_f12.png differ
diff --git a/web/icons/noble/components/avatar_head_f13.png b/web/icons/noble/components/avatar_head_f13.png
new file mode 100644
index 0000000..1e06d46
Binary files /dev/null and b/web/icons/noble/components/avatar_head_f13.png differ
diff --git a/web/icons/noble/components/avatar_head_f14.png b/web/icons/noble/components/avatar_head_f14.png
new file mode 100644
index 0000000..403795d
Binary files /dev/null and b/web/icons/noble/components/avatar_head_f14.png differ
diff --git a/web/icons/noble/components/avatar_head_f15.png b/web/icons/noble/components/avatar_head_f15.png
new file mode 100644
index 0000000..0b888ac
Binary files /dev/null and b/web/icons/noble/components/avatar_head_f15.png differ
diff --git a/web/icons/noble/components/avatar_head_f2.png b/web/icons/noble/components/avatar_head_f2.png
new file mode 100644
index 0000000..29e6c45
Binary files /dev/null and b/web/icons/noble/components/avatar_head_f2.png differ
diff --git a/web/icons/noble/components/avatar_head_f3.png b/web/icons/noble/components/avatar_head_f3.png
new file mode 100644
index 0000000..e04401d
Binary files /dev/null and b/web/icons/noble/components/avatar_head_f3.png differ
diff --git a/web/icons/noble/components/avatar_head_f4.png b/web/icons/noble/components/avatar_head_f4.png
new file mode 100644
index 0000000..8443631
Binary files /dev/null and b/web/icons/noble/components/avatar_head_f4.png differ
diff --git a/web/icons/noble/components/avatar_head_f5.png b/web/icons/noble/components/avatar_head_f5.png
new file mode 100644
index 0000000..af00697
Binary files /dev/null and b/web/icons/noble/components/avatar_head_f5.png differ
diff --git a/web/icons/noble/components/avatar_head_f6.png b/web/icons/noble/components/avatar_head_f6.png
new file mode 100644
index 0000000..7b5cfd9
Binary files /dev/null and b/web/icons/noble/components/avatar_head_f6.png differ
diff --git a/web/icons/noble/components/avatar_head_f7.png b/web/icons/noble/components/avatar_head_f7.png
new file mode 100644
index 0000000..01d33e5
Binary files /dev/null and b/web/icons/noble/components/avatar_head_f7.png differ
diff --git a/web/icons/noble/components/avatar_head_f8.png b/web/icons/noble/components/avatar_head_f8.png
new file mode 100644
index 0000000..5e77419
Binary files /dev/null and b/web/icons/noble/components/avatar_head_f8.png differ
diff --git a/web/icons/noble/components/avatar_head_f9.png b/web/icons/noble/components/avatar_head_f9.png
new file mode 100644
index 0000000..7b63a97
Binary files /dev/null and b/web/icons/noble/components/avatar_head_f9.png differ
diff --git a/web/icons/noble/components/avatar_head_m1.png b/web/icons/noble/components/avatar_head_m1.png
new file mode 100644
index 0000000..3cbd6ae
Binary files /dev/null and b/web/icons/noble/components/avatar_head_m1.png differ
diff --git a/web/icons/noble/components/avatar_head_m10.png b/web/icons/noble/components/avatar_head_m10.png
new file mode 100644
index 0000000..193c36a
Binary files /dev/null and b/web/icons/noble/components/avatar_head_m10.png differ
diff --git a/web/icons/noble/components/avatar_head_m11.png b/web/icons/noble/components/avatar_head_m11.png
new file mode 100644
index 0000000..249dc7e
Binary files /dev/null and b/web/icons/noble/components/avatar_head_m11.png differ
diff --git a/web/icons/noble/components/avatar_head_m12.png b/web/icons/noble/components/avatar_head_m12.png
new file mode 100644
index 0000000..3e75fd5
Binary files /dev/null and b/web/icons/noble/components/avatar_head_m12.png differ
diff --git a/web/icons/noble/components/avatar_head_m13.png b/web/icons/noble/components/avatar_head_m13.png
new file mode 100644
index 0000000..98f3162
Binary files /dev/null and b/web/icons/noble/components/avatar_head_m13.png differ
diff --git a/web/icons/noble/components/avatar_head_m14.png b/web/icons/noble/components/avatar_head_m14.png
new file mode 100644
index 0000000..bee2a1c
Binary files /dev/null and b/web/icons/noble/components/avatar_head_m14.png differ
diff --git a/web/icons/noble/components/avatar_head_m15.png b/web/icons/noble/components/avatar_head_m15.png
new file mode 100644
index 0000000..b618985
Binary files /dev/null and b/web/icons/noble/components/avatar_head_m15.png differ
diff --git a/web/icons/noble/components/avatar_head_m2.png b/web/icons/noble/components/avatar_head_m2.png
new file mode 100644
index 0000000..b2fda79
Binary files /dev/null and b/web/icons/noble/components/avatar_head_m2.png differ
diff --git a/web/icons/noble/components/avatar_head_m3.png b/web/icons/noble/components/avatar_head_m3.png
new file mode 100644
index 0000000..9abbef9
Binary files /dev/null and b/web/icons/noble/components/avatar_head_m3.png differ
diff --git a/web/icons/noble/components/avatar_head_m4.png b/web/icons/noble/components/avatar_head_m4.png
new file mode 100644
index 0000000..273ff28
Binary files /dev/null and b/web/icons/noble/components/avatar_head_m4.png differ
diff --git a/web/icons/noble/components/avatar_head_m5.png b/web/icons/noble/components/avatar_head_m5.png
new file mode 100644
index 0000000..35aa999
Binary files /dev/null and b/web/icons/noble/components/avatar_head_m5.png differ
diff --git a/web/icons/noble/components/avatar_head_m6.png b/web/icons/noble/components/avatar_head_m6.png
new file mode 100644
index 0000000..b9e2889
Binary files /dev/null and b/web/icons/noble/components/avatar_head_m6.png differ
diff --git a/web/icons/noble/components/avatar_head_m7.png b/web/icons/noble/components/avatar_head_m7.png
new file mode 100644
index 0000000..1eb0932
Binary files /dev/null and b/web/icons/noble/components/avatar_head_m7.png differ
diff --git a/web/icons/noble/components/avatar_head_m8.png b/web/icons/noble/components/avatar_head_m8.png
new file mode 100644
index 0000000..14eaacb
Binary files /dev/null and b/web/icons/noble/components/avatar_head_m8.png differ
diff --git a/web/icons/noble/components/avatar_head_m9.png b/web/icons/noble/components/avatar_head_m9.png
new file mode 100644
index 0000000..8e34feb
Binary files /dev/null and b/web/icons/noble/components/avatar_head_m9.png differ
diff --git a/web/icons/noble/components/avatar_mouth_f1.png b/web/icons/noble/components/avatar_mouth_f1.png
new file mode 100644
index 0000000..0691ac4
Binary files /dev/null and b/web/icons/noble/components/avatar_mouth_f1.png differ
diff --git a/web/icons/noble/components/avatar_mouth_f2.png b/web/icons/noble/components/avatar_mouth_f2.png
new file mode 100644
index 0000000..3c74b96
Binary files /dev/null and b/web/icons/noble/components/avatar_mouth_f2.png differ
diff --git a/web/icons/noble/components/avatar_mouth_f3.png b/web/icons/noble/components/avatar_mouth_f3.png
new file mode 100644
index 0000000..cb8ec3c
Binary files /dev/null and b/web/icons/noble/components/avatar_mouth_f3.png differ
diff --git a/web/icons/noble/components/avatar_mouth_f4.png b/web/icons/noble/components/avatar_mouth_f4.png
new file mode 100644
index 0000000..4e309ae
Binary files /dev/null and b/web/icons/noble/components/avatar_mouth_f4.png differ
diff --git a/web/icons/noble/components/avatar_mouth_f5.png b/web/icons/noble/components/avatar_mouth_f5.png
new file mode 100644
index 0000000..09d857b
Binary files /dev/null and b/web/icons/noble/components/avatar_mouth_f5.png differ
diff --git a/web/icons/noble/components/avatar_mouth_f6.png b/web/icons/noble/components/avatar_mouth_f6.png
new file mode 100644
index 0000000..bbb4935
Binary files /dev/null and b/web/icons/noble/components/avatar_mouth_f6.png differ
diff --git a/web/icons/noble/components/avatar_mouth_f7.png b/web/icons/noble/components/avatar_mouth_f7.png
new file mode 100644
index 0000000..4102ae5
Binary files /dev/null and b/web/icons/noble/components/avatar_mouth_f7.png differ
diff --git a/web/icons/noble/components/avatar_mouth_f8.png b/web/icons/noble/components/avatar_mouth_f8.png
new file mode 100644
index 0000000..94f43f1
Binary files /dev/null and b/web/icons/noble/components/avatar_mouth_f8.png differ
diff --git a/web/icons/noble/components/avatar_mouth_m1.png b/web/icons/noble/components/avatar_mouth_m1.png
new file mode 100644
index 0000000..eafb562
Binary files /dev/null and b/web/icons/noble/components/avatar_mouth_m1.png differ
diff --git a/web/icons/noble/components/avatar_mouth_m2.png b/web/icons/noble/components/avatar_mouth_m2.png
new file mode 100644
index 0000000..d93c1bd
Binary files /dev/null and b/web/icons/noble/components/avatar_mouth_m2.png differ
diff --git a/web/icons/noble/components/avatar_mouth_m3.png b/web/icons/noble/components/avatar_mouth_m3.png
new file mode 100644
index 0000000..57c7577
Binary files /dev/null and b/web/icons/noble/components/avatar_mouth_m3.png differ
diff --git a/web/icons/noble/components/avatar_mouth_m4.png b/web/icons/noble/components/avatar_mouth_m4.png
new file mode 100644
index 0000000..908cb0c
Binary files /dev/null and b/web/icons/noble/components/avatar_mouth_m4.png differ
diff --git a/web/icons/noble/components/avatar_mouth_m5.png b/web/icons/noble/components/avatar_mouth_m5.png
new file mode 100644
index 0000000..61cfd22
Binary files /dev/null and b/web/icons/noble/components/avatar_mouth_m5.png differ
diff --git a/web/icons/noble/components/avatar_mouth_m6.png b/web/icons/noble/components/avatar_mouth_m6.png
new file mode 100644
index 0000000..d73b4f3
Binary files /dev/null and b/web/icons/noble/components/avatar_mouth_m6.png differ
diff --git a/web/icons/noble/components/avatar_mouth_m7.png b/web/icons/noble/components/avatar_mouth_m7.png
new file mode 100644
index 0000000..2e77d09
Binary files /dev/null and b/web/icons/noble/components/avatar_mouth_m7.png differ
diff --git a/web/icons/noble/components/avatar_mouth_m8.png b/web/icons/noble/components/avatar_mouth_m8.png
new file mode 100644
index 0000000..3d7fdd9
Binary files /dev/null and b/web/icons/noble/components/avatar_mouth_m8.png differ
diff --git a/web/icons/noble/components/avatar_mustache_1.png b/web/icons/noble/components/avatar_mustache_1.png
new file mode 100644
index 0000000..73e9a51
Binary files /dev/null and b/web/icons/noble/components/avatar_mustache_1.png differ
diff --git a/web/icons/noble/components/avatar_necklace_1.png b/web/icons/noble/components/avatar_necklace_1.png
new file mode 100644
index 0000000..a683401
Binary files /dev/null and b/web/icons/noble/components/avatar_necklace_1.png differ
diff --git a/web/icons/noble/components/avatar_necklace_2.png b/web/icons/noble/components/avatar_necklace_2.png
new file mode 100644
index 0000000..e6f1be2
Binary files /dev/null and b/web/icons/noble/components/avatar_necklace_2.png differ
diff --git a/web/icons/noble/components/avatar_necklace_3.png b/web/icons/noble/components/avatar_necklace_3.png
new file mode 100644
index 0000000..5c9b157
Binary files /dev/null and b/web/icons/noble/components/avatar_necklace_3.png differ
diff --git a/web/icons/noble/components/avatar_necklace_4.png b/web/icons/noble/components/avatar_necklace_4.png
new file mode 100644
index 0000000..5428b4f
Binary files /dev/null and b/web/icons/noble/components/avatar_necklace_4.png differ
diff --git a/web/icons/noble/components/avatar_necklace_5.png b/web/icons/noble/components/avatar_necklace_5.png
new file mode 100644
index 0000000..a0060fb
Binary files /dev/null and b/web/icons/noble/components/avatar_necklace_5.png differ
diff --git a/web/icons/noble/components/avatar_necklace_6.png b/web/icons/noble/components/avatar_necklace_6.png
new file mode 100644
index 0000000..9bae53f
Binary files /dev/null and b/web/icons/noble/components/avatar_necklace_6.png differ
diff --git a/web/icons/noble/components/avatar_necklace_f7.png b/web/icons/noble/components/avatar_necklace_f7.png
new file mode 100644
index 0000000..9e50130
Binary files /dev/null and b/web/icons/noble/components/avatar_necklace_f7.png differ
diff --git a/web/icons/noble/components/avatar_necklace_f8.png b/web/icons/noble/components/avatar_necklace_f8.png
new file mode 100644
index 0000000..e99b5f3
Binary files /dev/null and b/web/icons/noble/components/avatar_necklace_f8.png differ
diff --git a/web/icons/noble/components/avatar_necklace_m7.png b/web/icons/noble/components/avatar_necklace_m7.png
new file mode 100644
index 0000000..947c851
Binary files /dev/null and b/web/icons/noble/components/avatar_necklace_m7.png differ
diff --git a/web/icons/noble/components/avatar_necklace_m8.png b/web/icons/noble/components/avatar_necklace_m8.png
new file mode 100644
index 0000000..04bc9fb
Binary files /dev/null and b/web/icons/noble/components/avatar_necklace_m8.png differ
diff --git a/web/icons/noble/components/avatar_pattern_1.png b/web/icons/noble/components/avatar_pattern_1.png
new file mode 100644
index 0000000..2f79332
Binary files /dev/null and b/web/icons/noble/components/avatar_pattern_1.png differ
diff --git a/web/icons/noble/components/avatar_pattern_10.png b/web/icons/noble/components/avatar_pattern_10.png
new file mode 100644
index 0000000..ea0ed08
Binary files /dev/null and b/web/icons/noble/components/avatar_pattern_10.png differ
diff --git a/web/icons/noble/components/avatar_pattern_11.png b/web/icons/noble/components/avatar_pattern_11.png
new file mode 100644
index 0000000..a691850
Binary files /dev/null and b/web/icons/noble/components/avatar_pattern_11.png differ
diff --git a/web/icons/noble/components/avatar_pattern_12.png b/web/icons/noble/components/avatar_pattern_12.png
new file mode 100644
index 0000000..bdac431
Binary files /dev/null and b/web/icons/noble/components/avatar_pattern_12.png differ
diff --git a/web/icons/noble/components/avatar_pattern_13.png b/web/icons/noble/components/avatar_pattern_13.png
new file mode 100644
index 0000000..58d61d7
Binary files /dev/null and b/web/icons/noble/components/avatar_pattern_13.png differ
diff --git a/web/icons/noble/components/avatar_pattern_14.png b/web/icons/noble/components/avatar_pattern_14.png
new file mode 100644
index 0000000..74ad716
Binary files /dev/null and b/web/icons/noble/components/avatar_pattern_14.png differ
diff --git a/web/icons/noble/components/avatar_pattern_15.png b/web/icons/noble/components/avatar_pattern_15.png
new file mode 100644
index 0000000..ce1bcad
Binary files /dev/null and b/web/icons/noble/components/avatar_pattern_15.png differ
diff --git a/web/icons/noble/components/avatar_pattern_16.png b/web/icons/noble/components/avatar_pattern_16.png
new file mode 100644
index 0000000..3302d1e
Binary files /dev/null and b/web/icons/noble/components/avatar_pattern_16.png differ
diff --git a/web/icons/noble/components/avatar_pattern_17.png b/web/icons/noble/components/avatar_pattern_17.png
new file mode 100644
index 0000000..42fef5f
Binary files /dev/null and b/web/icons/noble/components/avatar_pattern_17.png differ
diff --git a/web/icons/noble/components/avatar_pattern_18.png b/web/icons/noble/components/avatar_pattern_18.png
new file mode 100644
index 0000000..15b6a43
Binary files /dev/null and b/web/icons/noble/components/avatar_pattern_18.png differ
diff --git a/web/icons/noble/components/avatar_pattern_19.png b/web/icons/noble/components/avatar_pattern_19.png
new file mode 100644
index 0000000..6ab7ccc
Binary files /dev/null and b/web/icons/noble/components/avatar_pattern_19.png differ
diff --git a/web/icons/noble/components/avatar_pattern_2.png b/web/icons/noble/components/avatar_pattern_2.png
new file mode 100644
index 0000000..64b45c5
Binary files /dev/null and b/web/icons/noble/components/avatar_pattern_2.png differ
diff --git a/web/icons/noble/components/avatar_pattern_3.png b/web/icons/noble/components/avatar_pattern_3.png
new file mode 100644
index 0000000..5a058a9
Binary files /dev/null and b/web/icons/noble/components/avatar_pattern_3.png differ
diff --git a/web/icons/noble/components/avatar_pattern_4.png b/web/icons/noble/components/avatar_pattern_4.png
new file mode 100644
index 0000000..24fc92c
Binary files /dev/null and b/web/icons/noble/components/avatar_pattern_4.png differ
diff --git a/web/icons/noble/components/avatar_pattern_5.png b/web/icons/noble/components/avatar_pattern_5.png
new file mode 100644
index 0000000..787adba
Binary files /dev/null and b/web/icons/noble/components/avatar_pattern_5.png differ
diff --git a/web/icons/noble/components/avatar_pattern_6.png b/web/icons/noble/components/avatar_pattern_6.png
new file mode 100644
index 0000000..f4a6096
Binary files /dev/null and b/web/icons/noble/components/avatar_pattern_6.png differ
diff --git a/web/icons/noble/components/avatar_pattern_7.png b/web/icons/noble/components/avatar_pattern_7.png
new file mode 100644
index 0000000..b003445
Binary files /dev/null and b/web/icons/noble/components/avatar_pattern_7.png differ
diff --git a/web/icons/noble/components/avatar_pattern_8.png b/web/icons/noble/components/avatar_pattern_8.png
new file mode 100644
index 0000000..63380d8
Binary files /dev/null and b/web/icons/noble/components/avatar_pattern_8.png differ
diff --git a/web/icons/noble/components/avatar_pattern_9.png b/web/icons/noble/components/avatar_pattern_9.png
new file mode 100644
index 0000000..e4a3d1f
Binary files /dev/null and b/web/icons/noble/components/avatar_pattern_9.png differ
diff --git a/web/icons/noble/components/avatar_scar_1.png b/web/icons/noble/components/avatar_scar_1.png
new file mode 100644
index 0000000..f862478
Binary files /dev/null and b/web/icons/noble/components/avatar_scar_1.png differ
diff --git a/web/icons/noble/components/avatar_scar_2.png b/web/icons/noble/components/avatar_scar_2.png
new file mode 100644
index 0000000..d55f8b4
Binary files /dev/null and b/web/icons/noble/components/avatar_scar_2.png differ
diff --git a/web/icons/noble/components/avatar_sideburn_1.png b/web/icons/noble/components/avatar_sideburn_1.png
new file mode 100644
index 0000000..643a5d9
Binary files /dev/null and b/web/icons/noble/components/avatar_sideburn_1.png differ