1:- module(accordion, [accordion//2, accordion_section//2]).

Accordion widget

*/

    7:- use_module(library(http/html_write)).    8:- use_module(library(http/html_head)).    9
   10:- ensure_loaded(weblog(resources/resources)).   11
   12:- html_meta accordion(+, html, ?, ?).
   13:- predicate_options(accordion//2, 1, [
   14	collapsible(boolean),
   15	inactive(text),
   16	active(text),
   17	height(oneof([fill, content])),
   18	hoverintent(boolean),
   19	sortable(boolean)
   20	       ]).
 accordion(+Options:list, +HTML:html)// is det
Emit an accordion widget.

Works with library(http/html_write)

Uses the JQuery library

accordion has a structural similarity to the html ordered list tag

<OL>
     <LI>First Thing</LI>
     <LI>Second Thing</LI>
</OL>

in that an accordion expects a list of \accordion_section//2 inclusions

Example:

       thing_with_accordion -->
          html([
             h2('All of Acmes Fine Products'),
             \accordion([sortable(true)], [
                 \accordion_section('Acme Products #133 Portable Hole', [
                      p(img(src='portablehole.png', []),
                         'The Best hole for the money'),
                      p('Not recommended for use by coyotes')
                      ]),
                  ...
                  \accordion_section('Acme Products #17 Nuclear Bomb', [
                      p(img(src='nuke.png', []),
                         '27Kiloton Nuclear Bomb'),
                      p('The best road runner blaster on themarket') ])
             ])

Options:

collapsible(Collapsible)
By default, accordions always keep one section open. To allow the user to close all sections set collapsible(true).
inactive(Class)
If present, the option active(atom) is required. Inactive headers will receive the atom as an additional class.
active(Class)
If present, the active(atom) is required. Inactive headers will receive the atom as an additional class.
height(Style)
Because the accordion is comprised of block-level elements, by default its width fills the available horizontal space. To fill the vertical space allocated by its container set height(fill). To consume only as much space as is needed for content, set height(content) (the default). NOTE: If the containing box is resized after initial draw

 $( "#accordion" ).accordion( "refresh" );

must be called. See http://jqueryui.com/accordion/#fillspace

hover(Bool)
Open sections on hover. NOTE: This is broken in recent versions of jQuery
sortable(Bool)
Sections may be rearranged by dragging if sortable(true) is used, then each group of sections to be drug together must be surrounded by
      div(class=group, ... accordion_sections ... )
id(Name)
The outer div's html id (default accordion ). Accordions sharing a page need unique IDs.
css(Bool)
If true (default), include =/themes/base/jquery-ui.css= from the jquery CDN. Setting to false give a very bare boned H3 appearance to the headers, but does work. Set to false if you supply your own styling.

Note: currently not implemented.

Arguments:
Options- the list of options
HTML- the termerized HTML contents, which must be a list of accordian_section//2 sections
To be done
- implement css option. hover is broken.

*/

  117accordion(Options, _, _, _) :-
  118	option(inactive(_), Options),
  119	\+ option(active(_), Options),
  120	throw(error(domain_error(list, Options), context(accordion//2,
  121				   'inactive option demands active'))).
  122accordion(Options, _, _, _) :-
  123	option(active(_), Options),
  124	\+ option(inactive(_), Options),
  125	throw(error(domain_error(list, Options), context(accordion//2,
  126				   'active option demands inactive'))).
  127
  128accordion(Options, HTML) -->
  129	{
  130	    debug(weblog, 'accordion got ~q: ~q', [Options, HTML] ),
  131	    valid_accordion_html(HTML),
  132	    option(id(ID), Options, accordion),
  133	    phrase(accordion_javascript(Options), CScript),
  134	    atom_codes(AScript, CScript)
  135	},
  136	html([
  137	    \html_requires(jquery_ui),
  138	         div(id=ID, HTML),
  139	         script(AScript)
  140	     ]),
  141	!.
  142accordion(_, HTML, _, _) :-
  143	throw(error(domain_error(list, HTML),
  144		    context(accordion/2, 'Cannot generate HTML. Only \
  145accordion_section//2 can be direct child of accordion//2'))).
 valid_accordion_html(:HTML:html)
unifies if HTML is a list of accordion_section escapes with, possibly, div(class=group, blahblah)
  152valid_accordion_html(_:X) :-
  153	valid_accordion_html(X).
  154
  155valid_accordion_html([]).
  156valid_accordion_html([\accordion_section(_, _) | T]) :-
  157	valid_accordion_html(T).
  158
  159valid_accordion_html([\(_:accordion_section(_, _)) | T]) :-
  160	valid_accordion_html(T).
  161
  162valid_accordion_html(\accordion_section(_, _)).
  163valid_accordion_html(\(_:accordion_section(_, _))).
  164
  165% Allow containing divs for sort grouping
  166valid_accordion_html([div(_, HTML) | T]) :-
  167	valid_accordion_html(HTML),
  168	valid_accordion_html(T).
  169
  170
  171:- html_meta accordion_section(+, html, ?, ?).
 accordion_section(+Header:options, +HTML:html)// is det
Create an accordion section of the given header and body.
Arguments:
Header- atom text of header. In future may accept option(OptionList)
HTML- Termerized HTML for body
See also
- accordion//2

*/

  182accordion_section(Header, HTML) -->
  183	{
  184	    atomic(Header)
  185	},
  186	html([
  187			      h3(Header),
  188			      div(HTML)
  189	     ]).
  190
  191:- html_meta grouped_accordion_section(+, html, ?, ?).
 grouped_accordion_section(+Header:options, +HTML:html)// is det
Create an accordion section of the given header and body.

Note - don't use this, see the sortable option in accordion//2

Arguments:
Header- atom text of header. In future may accept option(OptionList)
HTML- Termerized HTML for body
See also
- accordion//2

*/

  204grouped_accordion_section(Header, HTML) -->
  205	{
  206	    atomic(Header)
  207	},
  208	html([
  209	    div(class=group, [
  210			      h3(Header),
  211			      div(class=group, HTML)
  212			     ])
  213	     ]).
  214
  215
  216accordion_javascript(Options) -->
  217	{
  218	    option(id(ID), Options, accordion),
  219	    atom_codes(ID, CID)
  220	},
  221	jquery_call_start,
  222	accordion_call_open(CID),
  223       accordion_call_options(Options),
  224       accordion_call_close,
  225       attached_calls(Options),
  226       ";\n",
  227       jquery_call_end,
  228       accordion_post_javascript(Options).
  229
  230accordion_call_open(CID) -->
  231	"    $( \"#",
  232        CID,
  233        "\" ).accordion({\n".
  234
  235accordion_call_close -->
  236       "dummy: 3\n})".
  237
  238jquery_call_start -->
  239       "  $(function() {\n".
  240
  241jquery_call_end -->
  242	"  });\n".
  243
  244accordion_call_options(Options) -->
  245       collapse_options(Options),
  246       icons_options(Options),
  247       fillspace_options(Options),
  248       hover_options(Options),
  249       sortable_options(Options).
  250
  251collapse_options(Options) -->
  252	{
  253	   option(collapsible(false), Options, false)
  254	},
  255	[],!.
  256collapse_options(_) -->
  257	"collapsible: true,\n".
  258
  259icons_options(Options) -->
  260	{
  261	   \+ option(active(_), Options)
  262	},
  263	[],!.
  264icons_options(Options) -->
  265	{
  266	   option(active(Active), Options),
  267	   option(inactive(Inactive), Options),
  268	   atom_codes(Active, CActive),
  269	   atom_codes(Inactive, CInactive)
  270	},
  271	"icons: {\n          header: \"",
  272	CInactive,
  273	"\",\n       activeHeader: \"",
  274	CActive,
  275	"\"\n     },\n".
  276
  277fillspace_options(Options) -->
  278	{
  279	   option(height(content), Options, content)
  280	},
  281	"heightStyle: \"content\",\n",
  282	!.
  283fillspace_options(_) -->
  284	"heightStyle: \"fill\",\n".
  285
  286hover_options(Options) -->
  287	{
  288	   option(hover(false), Options, false)
  289	},
  290	[],!.
  291hover_options(_) -->
  292	"event: \"click hoverintent\",\n".
  293
  294sortable_options(Options) -->
  295	{
  296	   option(sortable(false), Options, false)
  297	},
  298	[],!.
  299sortable_options(_) -->
  300	"header: \"> div > h3\",\n".
  301
  302attached_calls(Options) -->
  303	{
  304	   option(sortable(false), Options, false)
  305	},
  306	[],!.
  307attached_calls(_) -->
  308	".sortable({\n\c
  309        axis: \"y\",\n\c
  310        handle: \"h3\",\n\c
  311        stop: function( event, ui ) {\n\c
  312          // IE doesn't register the blur when sorting\n\c
  313          // so trigger focusout handlers to remove .ui-state-focus\n\c
  314          ui.item.children( \"h3\" ).triggerHandler( \"focusout\" );\n\c
  315        }})\n".
  316
  317accordion_post_javascript(Options) -->
  318	hover_post_options(Options).
  319
  320
  321hover_post_options(Options) -->
  322	{
  323	   option(hover(false), Options, false)
  324	},
  325	[],!.
  326hover_post_options(_) -->
  327"var cfg = ($.hoverintent = {\n\c
  328    sensitivity: 7,\n\c
  329    interval: 100\n\c
  330  });\n\c
  331 \n\c
  332  $.event.special.hoverintent = {
  333         setup: function() {
  334             $( this ).bind( 'mouseover', jQuery.event.special.hoverintent.handler );
  335         },
  336         teardown: function() {
  337             $( this ).unbind( 'mouseover', jQuery.event.special.hoverintent.handler );
  338         },
  339         handler: function( event ) {
  340             var currentX, currentY, timeout,
  341                 args = arguments,
  342                 target = $( event.target ),
  343                 previousX = event.pageX,
  344                 previousY = event.pageY;
  345
  346	     function track( event ) {
  347                 currentX = event.pageX;
  348                 currentY = event.pageY;
  349	     };
  350
  351             function clear() {
  352      	         target
  353                .unbind( 'mousemove', track )
  354                .unbind( 'mouseout', clear );
  355	         clearTimeout( timeout );
  356             }
  357
  358             function handler() {
  359                 var prop,
  360	             orig = event;
  361
  362                 if ( ( Math.abs( previousX - currentX ) +
  363	                Math.abs( previousY - currentY ) ) < 7 ) {
  364	                    clear();
  365
  366	                    event = $.Event( 'hoverintent' );
  367                            for ( prop in orig ) {
  368		                if ( !( prop in event ) ) {
  369		                    event[ prop ] = orig[ prop ];
  370                                }
  371	                    }
  372                            // Prevent accessing the original event since the new event
  373                            // is fired asynchronously and the old event is no longer
  374                            // usable (#6028)
  375                            delete event.originalEvent;
  376
  377                            target.trigger( event );
  378                 } else {
  379                     previousX = currentX;
  380                     previousY = currentY;
  381                     timeout = setTimeout( handler, 100 );
  382                 }
  383             }
  384
  385	     timeout = setTimeout( handler, 100 );
  386             target.bind({
  387                 mousemove: track,
  388                 mouseout: clear
  389             });
  390         }
  391};\n"