diff cpack/dml/skin/minimal.pl @ 0:718306e29690 tip

commiting public release
author Daniel Wolff
date Tue, 09 Feb 2016 21:05:06 +0100
parents
children
line wrap: on
line diff
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/cpack/dml/skin/minimal.pl	Tue Feb 09 21:05:06 2016 +0100
@@ -0,0 +1,198 @@
+/* Part of DML (Digital Music Laboratory)
+	Copyright 2014-2015 Samer Abdallah, University of London
+	 
+	This program is free software; you can redistribute it and/or
+	modify it under the terms of the GNU General Public License
+	as published by the Free Software Foundation; either version 2
+	of the License, or (at your option) any later version.
+
+	This program is distributed in the hope that it will be useful,
+	but WITHOUT ANY WARRANTY; without even the implied warranty of
+	MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+	GNU General Public License for more details.
+
+	You should have received a copy of the GNU General Public
+	License along with this library; if not, write to the Free Software
+	Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
+*/
+
+:- module(minimal, []).
+
+
+:- use_module(cliopatria(hooks)).
+:- use_module(skin(cliopatria)).
+:- use_module(components(menu)).
+:- use_module(components(simple_search)).
+
+:- use_module(library(http/html_write)).
+:- use_module(library(http/html_head)).
+:- use_module(library(lambda)).
+:- use_module(library(htmlutils)).
+% :- use_module(framework/pure, []).
+:- use_module(framework/kube, []).
+:- use_module(framework/bootstrap).
+
+:- set_prolog_flag(double_quotes,string).
+
+% :- set_setting(htmlutils:appname,"DML").
+:- googlefont(sourcepro,"Source+Sans+Pro:300,600|Source+Code+Pro:400,700").
+
+:- html_resource(font_awesome, 
+      [ virtual(true)
+      , requires("//maxcdn.bootstrapcdn.com/font-awesome/4.1.0/css/font-awesome.min.css")
+      ]).
+
+:- html_resource(css('minimal.css'), [ ordered(true), requires([bootstrap, kube('kube.css')]) ]).
+:- html_resource(css('minimal_doc.css'), [ requires([pldoc_css,css('minimal.css')]) ]).
+:- html_resource(css('minimal_http_doc.css'), [ requires(css('minimal_doc.css')) ]).
+:- html_resource(css('isearch_extra.css'), [ requires([css('minimal.css'),css('interactive_search.css')]) ]).
+  
+:- multifile user:body//2.
+
+user:body(user(App),Body) -->
+   {member(App,[search,isearch])},
+   use_font("Source Sans Pro",sourcepro),
+   use_font("pre, code, .code, .editor","Source Code Pro",sourcepro),
+   html_requires(css('isearch_extra.css')),
+   html(body(class(kubepage),Body)).
+
+style_style(cliopatria(http_help), 'margin-left:auto;margin-right:auto;width:95%;max-width:160ex') :- !.
+style_style(cliopatria(wide), 'margin-left:auto;margin-right:auto;width:90%').
+style_style(cliopatria(_), 'margin-left:auto;margin-right:auto;width:80%;max-width:105ex').
+style_style(pldoc(object(_)), 'margin-left:auto;margin-right:auto;width:80%;max-width:160ex') :- !.
+style_style(pldoc(_), 'margin-left:auto;margin-right:auto;width:80%;max-width:120ex') :- !.
+
+style_css(cliopatria(http_help), 'minimal_http_doc.css') :- !.
+style_css(pldoc(_), 'minimal_doc.css') :- !.
+style_css(_, 'minimal.css').
+
+cliopatria:page_body(cliopatria(bare), Body) --> !,
+   {debug(skin,"Serving page with style: ~w.\n",[plain])},
+   html_requires(css('minimal.css')),
+   use_font("Source Sans Pro",sourcepro),
+   use_font("pre, code, .code, .editor","Source Code Pro",sourcepro),
+   html(body(class=['kubepage',cliopatria], Body)).
+
+cliopatria:page_body(cliopatria(bare(http_doc)), Body) --> !,
+   {debug(skin,"Serving page with style: ~w.\n",[bare(http_doc)])},
+   html_requires(css('minimal_http_doc.css')),
+   use_font("Source Sans Pro",sourcepro),
+   use_font("pre, code, .code, .editor","Source Code Pro",sourcepro),
+   html(body(class=['kubepage',cliopatria], Body)).
+
+cliopatria:page_body(Style, Body) --> !,
+   {debug(skin,"Serving page with style: ~w.\n",[Style])},
+   {style_style(Style,BodyStyle), style_css(Style,CSS)},
+   html_post(head, meta([name(viewport), content("width-device-width,initial-scale=1")]) ),
+   html_requires(css(CSS)),
+   html_requires('//ajax.googleapis.com/ajax/libs/jquery/1.11.2/jquery.min.js'),
+
+   % html_requires(cliopatria),
+   %html_requires(kube('kube.css')),
+   use_font("Source Sans Pro",sourcepro),
+   use_font("pre, code, .code, .editor","Source Code Pro",sourcepro),
+
+   html(body( [ class=['kubepage',cliopatria]],
+
+              % Version with wide navbar
+              [ header(class=[group], div(style(BodyStyle), \clio_menu(inline_search)))
+              , div([ style(BodyStyle) ],
+                    [ div([id('cp-content'), class(content)], Body)
+
+              % Original version with narrow navbar
+              % [ div([ style(BodyStyle) ],
+              %       [ header(class=[group], \clio_menu(inline_search))
+              %       , div([id('cp-content'), class(content)], Body)
+
+                    , hr([style='margin-top:1em; margin-bottom:0.5em;',clear=all])
+                    , div([ style('font-size:smaller;text-align:right;')
+                          , id('cp-footer'), class(footer)], 
+                          \server_address('ClioPatria'))
+                    ])
+              ])).
+
+cliopatria:page_body(Style,_) -->
+   {debug(skin,"Not serving page with style ~w.\n",[Style]), fail}.
+
+
+clio_menu(full) -->
+   { findall(Key-Item, cp_menu:current_menu_item(Key, Item), Pairs0),
+     sort(Pairs0, Pairs),
+     group_pairs_by_key(Pairs, ByKey),
+     cp_menu:sort_menu_popups(ByKey, Menu),
+     maplist(translate_menu,Menu,Menu1)
+   },
+   navbar('DML',['navbar-static-top'],navbar_menu(left,seqmap(navbar_item,Menu1))),
+   minimal_search.
+
+clio_menu(inline_search) -->
+   { findall(Key-Item, cp_menu:current_menu_item(Key, Item), Pairs0),
+     sort(Pairs0, Pairs),
+     group_pairs_by_key(Pairs, ByKey),
+     cp_menu:sort_menu_popups(ByKey, Menu),
+     maplist(translate_menu,Menu,Menu1)
+   },
+   navbar('DML',['navbar-static-top'],
+      html([  \navbar_menu(left,seqmap(navbar_item,Menu1))
+           ,  span(class('navbar-form navbar-right'), div(class('form-group'),\minimal_search))
+           ])).
+
+
+translate_menu(_-[Item],Link) :-
+   translate_item(Item,Link).
+translate_menu(Key-Items,Menu) :-
+   cp_menu:menu_label(Key, Key, Label),
+   translate_dropdown(Label,Items,Menu).
+
+translate_dropdown(a(Attribs,Label),Items,menu(Label,[link('OpenID page',URL) | Items1])) :- !,
+   (Attribs=href(URL)-> true; memberchk(href(URL),Attribs)),
+   maplist(translate_item, Items, Items1).
+
+translate_dropdown(Label,Items,menu(Label,Items1)) :- 
+   maplist(translate_item,Items,Items1).
+
+translate_item(item(_,Spec,Label),link(Label,Location)) :- 
+   atom(Spec),
+   (  \+sub_atom(Spec, 0, _, _, 'http://'),
+      catch( http_dispatch:http_location_by_id(Spec, Location), E,
+             (print_message(informational, E), fail))
+   -> true
+   ;  Location = Spec
+   ).
+
+
+minimal_search -->
+   html_post(head,style( 
+      % ac_find_literal_container has class .yui-ac-container
+      [  ".yui-ac-content { background-color:#ffffff;padding:0ex;border: solid 1px #ddd;
+                            box-shadow:0 6px 12px rgba(0,0,0,.175);
+                            text-align:left; z-index:2;margin-top:1ex}"
+      ,  ".yui-ac-content { position:absolute;max-height:30em; overflow:auto; overflow-x:hidden; }"
+      ,  "input, select, input[type='search'], textarea { z-index:0 }"
+      ,  ".yui-ac-content ul {padding:0ex;margin:0ex;list-style-type:none}"
+      ,  ".yui-ac-content ul li {margin:0em;padding:0.5ex}"
+      ,  "li.yui-ac-highlight { background-color:#eee }"
+      % ,  "span.acmatch { background-color: #bbf; }"
+      ,  "span.acmatch { text-decoration:underline;
+                         text-decoration-color:#5ca9e4;
+                         -moz-text-decoration-color:#5ca9e4;}"
+      ,  "span.ac-builtin { color: blue; }"
+      ,  "span.ac-module { color: #888; }"
+      ,  "span.ac-exported { color: dark-green; }"
+      ,  "span.ac-private { color: red; }"
+      ,  "#search_form { margin-top:1ex; margin-bottom:1ex; text-align:right; }"
+      ,  "input#ac_find_literal_input { line-height:1.4em }"
+      ])),
+   html_post(head,script(type("text/javascript"),
+      "$(document).ready(function() { 
+         console.log('Adjusting search box...');
+         $('.yui-ac-input').attr('type','search').attr('placeholder','Search'); 
+         $('.yui-ac-input').css('box-sizing','border-box').css('width','26ex');
+         $('#ac_find_literal_complete').css('width','26ex');
+       });")),
+   html(form([ id(search_form), action(location_by_id(cpa_browse:search)) ],
+             [ \(cp_simple_search:search_box([ name(q) ]))
+             % , \cp_menu:filter([])
+             % , \cp_menu:select_handler([])
+             ])).
+