summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorYorhel <git@yorhel.nl>2020-10-25 12:02:35 +0100
committerYorhel <git@yorhel.nl>2020-10-28 09:32:45 +0100
commit960946ac90a8da32953a4a21128d993f2049f8d1 (patch)
treedcb9e0006c2afe79143141b1526d6ec7e11bc11a
parent3e3f36d3459d0db851c09315fcd74155735d9859 (diff)
Advsearch: Initial experiments with a new advanced search
Doing this on the main branch to make it easier to get early testing and feedback. Not like I have anything worth testing now, but it's not like this code is getting in the way of anything else. (Unless the changes broke something unrelated, in which case it's extra good to get that early testing)
-rw-r--r--data/style.css31
-rw-r--r--elm/AdvSearch/Main.elm125
-rw-r--r--elm/AdvSearch/Query.elm65
-rw-r--r--elm/AdvSearch/Set.elm68
-rw-r--r--elm/Lib/DropDown.elm2
-rw-r--r--lib/VNWeb/AdvSearch.pm133
-rw-r--r--lib/VNWeb/Releases/Lib.pm16
-rw-r--r--lib/VNWeb/VN/List.pm40
8 files changed, 462 insertions, 18 deletions
diff --git a/data/style.css b/data/style.css
index 95358b13..34281daa 100644
--- a/data/style.css
+++ b/data/style.css
@@ -74,24 +74,26 @@ div.warning h2, div.notice h2 { font-size: 13px; font-weight: bold; margin: 0; }
.elm_dd > a:hover > span:last-child > i,
.elm_dd > a:focus > span:last-child > i { visibility: visible }
.elm_dd > div { position: relative; float: right; width: 0; height: 0 }
-.elm_dd > div > ul { position: absolute; right: -10px; top: 0; border: 1px solid $border$; background-color: $secbg$; z-index: 1000; list-style-type: none; margin: 0; padding: 0; max-width: 400px; overflow: hidden }
+.elm_dd > div > div { position: absolute; right: -10px; top: 0; border: 1px solid $border$; background-color: $secbg$; z-index: 1000; margin: 0; padding: 0; max-width: 400px }
.elm_dd.search > div { float: left }
-.elm_dd.search > div > ul { right: auto; left: 0; top: 23px }
-.elm_dd > div > ul li { white-space: nowrap }
-.elm_dd > div > ul li a { display: block; border: 0; padding: 3px 5px 3px 3px }
-.elm_dd > div > ul li a.active,
-.elm_dd > div > ul li a:hover { background: $boxbg$ }
-.elm_dd > div > ul li p { white-space: normal; padding: 3px 5px 3px 3px }
-.elm_dd > div > ul li.separator { margin-bottom: 22px }
+.elm_dd.search ul { right: auto; left: 0; top: 23px }
+.elm_dd ul { width: 100%; list-style-type: none; margin: 0; padding: 0 }
+.elm_dd ul li { white-space: nowrap }
+.elm_dd ul li a { display: block; border: 0; padding: 3px 5px 3px 3px }
+.elm_dd ul li a.active,
+.elm_dd ul li a:hover { background: $boxbg$ }
+.elm_dd ul li p { white-space: normal; padding: 3px 5px 3px 3px }
+.elm_dd ul li.separator { margin-bottom: 22px }
+
.maintabs .elm_dd > a { box-sizing: border-box; height: 21px; padding: 1px 15px 0 7px; border: 1px solid $border$; border-bottom: none; background-color: $tabbg$; color: $maintext$ }
-.elm_votedd .elm_dd > div > ul li { text-align: left }
+.elm_votedd .elm_dd ul li { text-align: left }
.elm_dd_input .elm_dd > a { background-color: $secbg$; color: $maintext$; border: 1px solid $secborder$; font: 14px "Tahoma", "Arial", sans-serif; padding: 1px 15px 1px 2px; margin: -1px }
.elm_dd_noarrow .elm_dd > a { padding-right: 0 }
.elm_dd_noarrow .elm_dd > a > span:last-child { display: none }
.elm_dd_hover .elm_dd > div { display: none }
.elm_dd_hover .elm_dd:hover > div { display: block }
.elm_dd_left .elm_dd > div { float: left }
-.elm_dd_left .elm_dd > div > ul { right: 0; top: -20px }
+.elm_dd_left .elm_dd > div > div { right: 0; top: -20px }
.elm_dd_relextlink .elm_dd > a { padding-left: 4px; color: $link$ }
.elm_dd_relextlink ul a { text-align: right }
.elm_dd_relextlink ul span { color: $maintext$; padding-right: 10px }
@@ -1108,6 +1110,15 @@ p.filselect i { font-style: normal }
+
+/****** Advanced Search *******/
+
+.advsearch { width: 90%; margin: 0 5%; }
+.advsearch .quickselect { width: 100%; display: flex; justify-content: center }
+.advsearch .quickselect > * { margin: 5px; width: 150px }
+
+
+
/****** Image flagging *******/
/* divs:
diff --git a/elm/AdvSearch/Main.elm b/elm/AdvSearch/Main.elm
new file mode 100644
index 00000000..abd8017c
--- /dev/null
+++ b/elm/AdvSearch/Main.elm
@@ -0,0 +1,125 @@
+module AdvSearch.Main exposing (main)
+
+-- TODO: This is a quick'n'dirty proof of concept, most of the functionality in
+-- here needs to be abstracted so that we can query more than just the
+-- language field.
+
+import Html exposing (..)
+import Html.Attributes exposing (..)
+import Html.Events exposing (..)
+import Browser
+import Set
+import Json.Encode as JE
+import Json.Decode as JD
+import Lib.DropDown as DD
+import Lib.Api as Api
+import Lib.Html exposing (..)
+import Lib.Util exposing (..)
+import Gen.Types as GT
+import AdvSearch.Query exposing (..)
+
+main : Program JE.Value Model Msg
+main = Browser.element
+ { init = \e -> (init e, Cmd.none)
+ , view = view
+ , update = update
+ , subscriptions = \m -> DD.sub m.langDd
+ }
+
+
+type alias Model =
+ { langSel : Set.Set String
+ , langDd : DD.Config Msg
+ , langAnd : Bool
+ , langNeg : Bool
+ }
+
+
+init : JE.Value -> Model
+init v = JD.decodeValue decodeQuery v |> Result.toMaybe |> Maybe.andThen query2Model |> Maybe.withDefault
+ { langSel = Set.empty
+ , langDd = DD.init "adv_lang" LangToggle
+ , langAnd = False
+ , langNeg = False
+ }
+
+
+model2Query : Model -> Maybe Query
+model2Query m =
+ case (m.langNeg, m.langAnd, Set.toList m.langSel) of
+ (_,_,[]) -> Nothing
+ (n,_,[v]) -> Just <| QStr "lang" (if n then Ne else Eq) v
+ (False, False, l) -> Just <| QOr <| List.map (\v -> QStr "lang" Eq v) l
+ (True , False, l) -> Just <| QAnd <| List.map (\v -> QStr "lang" Ne v) l
+ (False, True , l) -> Just <| QAnd <| List.map (\v -> QStr "lang" Eq v) l
+ (True , True , l) -> Just <| QOr <| List.map (\v -> QStr "lang" Ne v) l
+
+
+-- Only recognizes queries generated with model2Query, doesn't handle alternative query structures.
+query2Model : Query -> Maybe Model
+query2Model q =
+ let m and neg l = Just { langSel = Set.fromList l, langAnd = xor neg and, langNeg = neg, langDd = DD.init "adv_lang" LangToggle }
+ single and qs =
+ case qs of
+ QStr "lang" Eq v -> m and False [v]
+ QStr "lang" Ne v -> m and True [v]
+ _ -> Nothing
+ lst and qs xqs =
+ case (qs, xqs) of
+ (_, []) -> single and qs
+ (QStr "lang" op _, QStr "lang" opn v :: xs) -> if op /= opn then Nothing else Maybe.map (\model -> { model | langSel = Set.insert v model.langSel }) (lst and qs xs)
+ _ -> Nothing
+ in case q of
+ QAnd (x::xs) -> lst True x xs
+ QOr (x::xs) -> lst False x xs
+ _ -> single False q
+
+
+type Msg
+ = LangToggle Bool
+ | LangSel String Bool
+ | LangAnd Bool
+ | LangNeg Bool
+
+update : Msg -> Model -> (Model, Cmd Msg)
+update msg model =
+ case msg of
+ LangToggle b -> ({ model | langDd = DD.toggle model.langDd b }, Cmd.none)
+ LangSel s b -> ({ model | langSel = if b then Set.insert s model.langSel else Set.remove s model.langSel }, Cmd.none)
+ LangAnd b -> ({ model | langAnd = b }, Cmd.none)
+ LangNeg b -> ({ model | langNeg = b }, Cmd.none)
+
+
+view : Model -> Html Msg
+view model = div [ class "advsearch" ]
+ [ input [ type_ "hidden", id "f", name "f", value <| Maybe.withDefault "" <| Maybe.map (\v -> JE.encode 0 (encodeQuery v)) (model2Query model) ] []
+ , div [ class "quickselect" ]
+ [ div [ class "elm_dd_input" ]
+ [ DD.view model.langDd Api.Normal
+ (case Set.size model.langSel of
+ 0 -> b [ class "grayedout" ] [ text "Language" ]
+ 1 -> text <| Maybe.withDefault "" <| lookup (Set.toList model.langSel |> List.head |> Maybe.withDefault "") GT.languages
+ n -> text <| "Language (" ++ String.fromInt n ++ ")")
+ <| \() -> -- TODO: Styling & single-selection mode
+ [ div []
+ [ linkRadio model.langAnd LangAnd [ text "and" ]
+ , text " / "
+ , linkRadio (not model.langAnd) (\b -> LangAnd (not b)) [ text "or" ]
+ ]
+ , div []
+ [ linkRadio (not model.langNeg) (\b -> LangNeg (not b)) [ text "include" ]
+ , text " / "
+ , linkRadio model.langNeg LangNeg [ text "exclude" ]
+ ]
+ , ul [ style "columns" "2"] <| List.map (\(l,t) -> li [] [ linkRadio (Set.member l model.langSel) (LangSel l) [ langIcon l, text t ] ]) GT.languages
+ ]
+ ]
+ , input [ type_ "button", class "submit", value "Advanced mode" ] [] -- TODO: Advanced mode where you can construct arbitrary queries.
+ , input [ type_ "submit", class "submit", value "Search" ] []
+ ]
+ , pre []
+ [ text <| Maybe.withDefault "" <| Maybe.map (\v -> JE.encode 2 (encodeQuery v)) (model2Query model)
+ , br [] [], br [] []
+ , text <| Maybe.withDefault "" <| Maybe.map (\v -> JE.encode 2 (encodeQuery v)) <| Maybe.andThen (\nm -> model2Query nm) <| Maybe.andThen (\q -> query2Model q) (model2Query model)
+ ]
+ ]
diff --git a/elm/AdvSearch/Query.elm b/elm/AdvSearch/Query.elm
new file mode 100644
index 00000000..b2ea12ac
--- /dev/null
+++ b/elm/AdvSearch/Query.elm
@@ -0,0 +1,65 @@
+module AdvSearch.Query exposing (..)
+
+import Json.Encode as JE
+import Json.Decode as JD
+
+-- Generic dynamically typed representation of a query.
+-- Used only as an intermediate format to help with encoding/decoding.
+type Op = Eq | Ne | Ge | Le
+type Query
+ = QAnd (List Query)
+ | QOr (List Query)
+ | QInt String Op Int
+ | QStr String Op String
+ | QQuery String Op Query
+
+
+encodeOp : Op -> JE.Value
+encodeOp o = JE.string <|
+ case o of
+ Eq -> "="
+ Ne -> "!="
+ Ge -> ">="
+ Le -> "<="
+
+encodeQuery : Query -> JE.Value
+encodeQuery q =
+ case q of
+ QAnd l -> JE.list identity (JE.string "and" :: List.map encodeQuery l)
+ QOr l -> JE.list identity (JE.string "or" :: List.map encodeQuery l)
+ QInt s o a -> JE.list identity [JE.string s, encodeOp o, JE.int a]
+ QStr s o a -> JE.list identity [JE.string s, encodeOp o, JE.string a]
+ QQuery s o a -> JE.list identity [JE.string s, encodeOp o, encodeQuery a]
+
+
+
+-- Drops the first item in the list, decodes the rest
+decodeQList : JD.Decoder (List Query)
+decodeQList =
+ let dec l = List.map (JD.decodeValue decodeQuery) (List.drop 1 l) -- [Result Query]
+ f v r = Result.andThen (\a -> Result.map (\e -> (e::a)) v) r -- Result Query -> Result [Query] -> Result [Query]
+ res l = case List.foldr f (Ok []) (dec l) of -- Decoder [Query]
+ Err e -> JD.fail (JD.errorToString e)
+ Ok v -> JD.succeed v
+ in JD.list JD.value |> JD.andThen res -- [Value]
+
+decodeOp : JD.Decoder Op
+decodeOp = JD.string |> JD.andThen (\s ->
+ case s of
+ "=" -> JD.succeed Eq
+ "!=" -> JD.succeed Ne
+ ">=" -> JD.succeed Ge
+ "<=" -> JD.succeed Le
+ _ -> JD.fail "Invalid operator")
+
+decodeQuery : JD.Decoder Query
+decodeQuery = JD.index 0 JD.string |> JD.andThen (\s ->
+ case s of
+ "and" -> JD.map QAnd decodeQList
+ "or" -> JD.map QOr decodeQList
+ _ -> JD.oneOf
+ [ JD.map2 (QInt s ) (JD.index 1 decodeOp) (JD.index 2 JD.int)
+ , JD.map2 (QStr s ) (JD.index 1 decodeOp) (JD.index 2 JD.string)
+ , JD.map2 (QQuery s) (JD.index 1 decodeOp) (JD.index 2 decodeQuery)
+ ]
+ )
diff --git a/elm/AdvSearch/Set.elm b/elm/AdvSearch/Set.elm
new file mode 100644
index 00000000..1320036d
--- /dev/null
+++ b/elm/AdvSearch/Set.elm
@@ -0,0 +1,68 @@
+-- Attempt to abstract away a single widget for set-style selections.
+
+module AdvSearch.Set exposing (..)
+
+import Html exposing (..)
+import Html.Attributes exposing (..)
+import Html.Events exposing (..)
+import Set
+import Lib.DropDown as DD
+import Lib.Api as Api
+import Lib.Html exposing (..)
+import Lib.Util exposing (..)
+import Gen.Types as GT
+
+
+type alias Model a =
+ { sel : Set.Set a
+ , dd : DD.Config (Msg a)
+ , and : Bool
+ , neg : Bool
+ }
+
+type Msg a
+ = Toggle Bool
+ | Sel a Bool
+ | And Bool
+ | Neg Bool
+
+
+init : Bool -> String -> Model a
+init id =
+ { sel = Set.empty
+ , dd = DD.init id Toggle
+ , and = False
+ , neg = False
+ }
+
+update : Msg a -> Model a -> (Model a, Cmd (Msg a))
+update msg model =
+ case msg of
+ Toggle b -> ({ model | dd = DD.toggle model.dd b }, Cmd.none)
+ Sel s b -> ({ model | sel = if b then Set.insert s model.sel else Set.remove s model.sel }, Cmd.none)
+ And b -> ({ model | and = b }, Cmd.none)
+ Neg b -> ({ model | neg = b }, Cmd.none)
+
+
+view : Bool -> String -> List a -> (a -> List (Html (Msg a))) -> Model a -> Html (Msg a)
+view canAnd ddLabel items itemView model = div [ class "elm_dd_input" ]
+ [ DD.view model.dd Api.Normal
+ (case Set.size model.sel of
+ 0 -> b [ class "grayedout" ] [ text ddLabel ]
+ 1 -> span [] (Set.toList model.sel |> List.head |> Maybe.map itemView |> Maybe.withDefault [])
+ n -> text <| ddLabel ++ " (" ++ String.fromInt n ++ ")")
+ <| \() -> -- TODO: Styling
+ [ if not canAnd then text "" else div []
+ [ linkRadio model.and And [ text "and" ]
+ , text " / "
+ , linkRadio (not model.and) (\b -> And (not b)) [ text "or" ]
+ ]
+ , div []
+ [ linkRadio (not model.neg) (\b -> Neg (not b)) [ text "include" ]
+ , text " / "
+ , linkRadio model.neg Neg [ text "exclude" ]
+ ]
+ --, ul [ style "columns" "2"] <| List.map (\(l,t) -> li [] [ linkRadio (Set.member l model.langSel) (LangSel l) [ langIcon l, text t ] ]) GT.languages
+ , ul [ style "columns" "2"] <| List.map (\l -> li [] [ linkRadio (Set.member l model.sel) (Sel l) (itemView l) ]) items
+ ]
+ ]
diff --git a/elm/Lib/DropDown.elm b/elm/Lib/DropDown.elm
index 1e6204ac..3de02f11 100644
--- a/elm/Lib/DropDown.elm
+++ b/elm/Lib/DropDown.elm
@@ -64,5 +64,5 @@ view conf status lbl cont =
Api.Loading -> [ lbl, span [] [ span [ class "spinner" ] [] ] ]
Api.Error e -> [ b [ class "standout" ] [ text "error" ], span [] [ i [] [ text "▾" ] ] ]
, div [ classList [("hidden", not conf.opened)] ]
- <| if conf.opened then cont () else [ text "" ]
+ [ if conf.opened then div [] (cont ()) else text "" ]
]
diff --git a/lib/VNWeb/AdvSearch.pm b/lib/VNWeb/AdvSearch.pm
new file mode 100644
index 00000000..c8efa87b
--- /dev/null
+++ b/lib/VNWeb/AdvSearch.pm
@@ -0,0 +1,133 @@
+package VNWeb::AdvSearch;
+
+use v5.26;
+use TUWF;
+use Exporter 'import';
+use VNWeb::DB;
+use VNWeb::Validation;
+use VNWeb::HTML;
+use VNDB::Types;
+
+our @EXPORT = qw/ as_tosql as_elm_ /;
+
+
+# Search query (JSON):
+#
+# $Query = $Combinator || $Predicate
+# $Combinator = [ 'and'||'or', $Query, .. ]
+# $Predicate = [ $Field, $Op, $Value ]
+# $Op = '=', '!=', '>=', '<='
+# $Value = $integer || $string || $Query
+#
+# Accepted values for $Op and $Value depend on $Field.
+#
+# e.g.
+#
+# [ 'and'
+# , [ 'or' # No support for array values, so IN() queries need explicit ORs.
+# , [ '=', 'lang', 'en' ]
+# , [ '=', 'lang', 'de' ]
+# , [ '=', 'lang', 'fr' ]
+# ]
+# , [ '!=', 'olang', 'ja' ]
+# , [ '=', 'char', [ 'and' # VN has a char that matches the given query
+# , [ '>=', 'bust', 40 ]
+# , [ '<=', 'bust', 100 ]
+# ]
+# ]
+# ]
+#
+# Search queries should be seen as some kind of low-level assembly for
+# generating complex queries, they're designed to be simple to implement,
+# powerful, extendable and stable. They're also a pain to work with, but that
+# comes with the trade-off.
+#
+# TODO: Compact search query encoding for in URLs. Passing around JSON is... ugly.
+
+
+# Define a $Field, args:
+# $type -> 'v', 'c', etc.
+# $name -> $Field name
+# $value -> TUWF::Validate schema for value validation, or $query_type to accept a nested query.
+# $op=>$sql -> Operator definitions and sql() generation functions.
+#
+# An implementation for the '!=' operator will be supplied automatically if it's not explicitely defined.
+my %fields;
+sub f {
+ my($t, $n, $v, %op) = @_;
+ my %f = (
+ value => ref $v eq 'HASH' ? tuwf->compile($v) : $v,
+ op => \%op,
+ );
+ $f{op}{'!='} = sub { sql 'NOT (', $f{op}{'='}->(@_), ')' } if $f{op}{'='} && !$f{op}{'!='};
+ $f{int} = $f{value} && ($f{value}->analyze->{type} eq 'int' || $f{value}->analyze->{type} eq 'bool');
+ $fields{$t}{$n} = \%f;
+}
+
+f 'v', 'lang', { enum => \%LANGUAGE }, '=' => sub { sql 'v.c_languages && ARRAY', \$_, '::language[]' };
+f 'v', 'olang', { enum => \%LANGUAGE }, '=' => sub { sql 'v.c_olang && ARRAY', \$_, '::language[]' };
+f 'v', 'plat', { enum => \%PLATFORM }, '=' => sub { sql 'v.c_platforms && ARRAY', \$_, '::platform[]' };
+
+
+
+sub validate {
+ my($t, $q) = @_;
+ return { msg => 'Invalid query' } if ref $q ne 'ARRAY' || @$q < 2 || !defined $q->[0] || ref $q->[0];
+
+ # combinator
+ if($q->[0] eq 'and' || $q->[0] eq 'or') {
+ for(@$q[1..$#$q]) {
+ my $r = validate($t, $_);
+ return $r if !$r || ref $r;
+ }
+ return 1;
+ }
+
+ # predicate
+ return { msg => 'Invalid predicate' } if @$q != 3 || !defined $q->[1] || ref $q->[1];
+ my $f = $fields{$t}{$q->[0]};
+ return { msg => 'Unknown field', field => $q->[0] } if !$f;
+ return { msg => 'Invalid operator', field => $q->[0], op => $q->[1] } if !$f->{op}{$q->[1]};
+ return validate($f->{value}, $q->[2]) if !ref $f->{value};
+ my $r = $f->{value}->validate($q->[2]);
+ return { msg => 'Invalid value', field => $q->[0], value => $q->[2], error => $r->err } if $r->err;
+ $q->[2] = $r->data;
+ 1
+}
+
+
+# 'advsearch' validation, accepts either a JSON representation or an already decoded array.
+TUWF::set('custom_validations')->{advsearch} = sub { my($t) = @_; +{ required => 0, type => 'any', func => sub {
+ return { msg => 'Invalid JSON', error => $@ =~ s{[\s\r\n]* at /[^ ]+ line.*$}{}smr } if !ref $_[0] && !eval { $_[0] = JSON::XS->new->decode($_[0]); 1 };
+ validate($t, @_)
+} } };
+
+
+sub as_tosql {
+ my($t, $q) = @_;
+ return sql_and map as_tosql($t, $_), @$q[1..$#$q] if $q->[0] eq 'and';
+ return sql_or map as_tosql($t, $_), @$q[1..$#$q] if $q->[0] eq 'or';
+
+ my $f = $fields{$t}{$q->[0]};
+ local $_ = ref $f->{value} ? $q->[2] : as_tosql($f->{value}, $q->[2]);
+ $f->{op}{$q->[1]}->();
+}
+
+
+sub coerce_for_json {
+ my($t, $q) = @_;
+ if($q->[0] eq 'and' || $q->[0] eq 'or') {
+ coerce_for_json($t, $_) for @$q[1..$#$q];
+ } else {
+ my $f = $fields{$t}{$q->[0]};
+ $f->{int} ? $q->[2]*1 : ref $f->{value} ? "$q->[2]" : coerce_for_json($t, $q->[2]);
+ }
+ $q
+}
+
+sub as_elm_ {
+ my($t, $q) = @_;
+ elm_ 'AdvSearch.Main', 'raw', $q && coerce_for_json($t, $q);
+}
+
+1;
diff --git a/lib/VNWeb/Releases/Lib.pm b/lib/VNWeb/Releases/Lib.pm
index 4aad7b50..5be64efd 100644
--- a/lib/VNWeb/Releases/Lib.pm
+++ b/lib/VNWeb/Releases/Lib.pm
@@ -52,13 +52,15 @@ sub release_extlinks_ {
abbr_ class => 'icons external', title => 'External link', '';
};
div_ sub {
- ul_ sub {
- li_ sub {
- a_ href => $_->[1], sub {
- span_ $_->[2] if length $_->[2];
- txt_ $_->[0];
- }
- } for $r->{extlinks}->@*;
+ div_ sub {
+ ul_ sub {
+ li_ sub {
+ a_ href => $_->[1], sub {
+ span_ $_->[2] if length $_->[2];
+ txt_ $_->[0];
+ }
+ } for $r->{extlinks}->@*;
+ }
}
}
}
diff --git a/lib/VNWeb/VN/List.pm b/lib/VNWeb/VN/List.pm
new file mode 100644
index 00000000..a9cf6fb4
--- /dev/null
+++ b/lib/VNWeb/VN/List.pm
@@ -0,0 +1,40 @@
+package VNWeb::VN::List;
+
+use VNWeb::Prelude;
+use VNWeb::AdvSearch;
+
+
+TUWF::get qr{/experimental/v}, sub {
+ my $opt = tuwf->validate(get =>
+ q => { onerror => '' },
+ p => { upage => 1 },
+ f => { advsearch => 'v' },
+ )->data;
+
+ my $where = sql_and
+ 'NOT v.hidden',
+ $opt->{q} ? map sql('v.c_search LIKE', \"%$_%"), normalize_query $opt->{q} : (),
+ $opt->{f} ? as_tosql(v => $opt->{f}) : ();
+
+ my $time = time;
+ my $count = tuwf->dbVali('SELECT count(*) FROM vn v WHERE', $where);
+ $time = time - $time;
+
+ framework_ title => 'Browse visual novels', sub {
+ div_ class => 'mainbox', sub {
+ h1_ 'Browse visual novels';
+ div_ class => 'warning', sub {
+ h2_ 'EXPERIMENTAL';
+ p_ "This is Yorhel's playground. Lots of functionality is missing, lots of stuff is or will be broken. Here be dragons. Etc.";
+ };
+ br_;
+ form_ action => '/experimental/v', method => 'get', sub {
+ searchbox_ v => $opt->{q};
+ as_elm_ v => $opt->{f};
+ };
+ p_ sprintf '%d results in %.3fs', $count, $time;
+ };
+ };
+};
+
+1;