~alcinnz/amphiarao

a52109529e3af8433a574eb10d00e435f0bc9b09 — Adrian Cochrane 3 years ago a610435
Show search queries in existing searchbox, not new one.
2 files changed, 6 insertions(+), 6 deletions(-)

M src/Main.hs
M src/UI/Templates.hs
M src/Main.hs => src/Main.hs +1 -3
@@ 122,10 122,8 @@ searchSession session = do
    results <- forM Q.engines $ \(header, engine) -> do
        results' <- liftIO $ engine q session session'
        return (header, labelEmpty results')
    Tpl.inspector ok (Txt.pack ('🔎':q)) session' $ \langs -> H.main $ do
    Tpl.inspector' q ok (Txt.pack ('🔎':q)) session' $ \langs -> H.main $ do
        H.aside $ do
            H.form $ do
                H.input H.! A.type_ "search" H.! A.name "q" H.! A.value (H.stringValue q)
            H.dl $ do
                forM results $ \(header, results') -> do
                    H.dt $ header langs

M src/UI/Templates.hs => src/UI/Templates.hs +5 -3
@@ 1,5 1,5 @@
{-# LANGUAGE OverloadedStrings, ScopedTypeVariables #-}
module UI.Templates(page, inspector, sessionForm,
module UI.Templates(page, inspector, inspector', sessionForm,
    xmlNode, xmlNode', elSelector, elPage) where

import Happstack.Lite


@@ 31,7 31,9 @@ page return' title class_ body' = do
        body ! A.class_ class_ $ body' langs

inspector :: (Response -> ServerPart Response) -> Text -> Session' -> ([Text] -> Html) -> ServerPart Response
inspector return' title session' body' = do
inspector = inspector' ""
inspector' :: String -> (Response -> ServerPart Response) -> Text -> Session' -> ([Text] -> Html) -> ServerPart Response
inspector' q return' title session' body' = do
    let timeout = H.stringValue $ show $ pageLoad $ timeouts session'
    page return' [title, pack $ show $ currentURL $ session', "Amphiarao"] "fill" $ \langs -> do
        header $ do


@@ 40,7 42,7 @@ inspector return' title session' body' = do
            postButton "/nav/reload" (l' langs Reload') "↻"
            hr
            H.form ! action' ["/", uuid', "/search"] ! alt (l' langs Search') $ do
                input ! type_ "search" ! name "q" ! placeholder (l' langs Search')
                input ! type_ "search" ! name "q" ! value (stringValue q) ! placeholder (l' langs Search')
        body' langs
        footer $ do
            H.form ! action' ["/close/", uuid'] ! A.method "POST" ! alt (l' langs CloseSession') $ do