@@ 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
@@ 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