Compare commits

..

2 Commits

Author SHA1 Message Date
towards-a-new-leftypol c8f720f05b Searched posts show up as a CatalogGrid
- but not many posts have an attachment, so I might have to fix things
2024-03-02 03:03:25 -05:00
towards-a-new-leftypol 534ac9075c Saving search query using MVar and waiting for that MVar on form submit 2024-03-01 23:43:03 -05:00
4 changed files with 46 additions and 13 deletions

View File

@ -1,7 +1,7 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
module Component.CatalogGrid module Component.CatalogGrid
( Model ( Model (..)
, initialModel , initialModel
, Action (..) , Action (..)
, Interface (..) , Interface (..)

View File

@ -25,22 +25,34 @@ import Miso
, (<#) , (<#)
, consoleLog , consoleLog
, noEff , noEff
, batchEff
) )
import Data.JSString (pack) import Data.JSString (pack)
import qualified Network.Client as Client import qualified Network.Client as Client
import Network.Http (HttpResult (..)) import Network.Http (HttpResult (..))
import Control.Concurrent.MVar (tryTakeMVar, takeMVar, putMVar, swapMVar)
import Component.Search.SearchTypes import Component.Search.SearchTypes
update :: Interface a -> Action -> Model -> Effect a Model update :: Interface a -> Action -> Model -> Effect a Model
update iface (SearchChange q) model = model { searchTerm = q } <# do update iface (SearchChange q) model = model { searchTerm = q } <# do
consoleLog q consoleLog $ "SearchChange " <> q
m_search_query <- tryTakeMVar (searchVar model)
case m_search_query of
Nothing -> putMVar (searchVar model) q
Just _ -> swapMVar (searchVar model) q >> return ()
return $ (passAction iface) NoAction return $ (passAction iface) NoAction
update iface (OnSubmit search_query) model = model { searchTerm = search_query } <# do update iface OnSubmit model = model <# do
search_query <- takeMVar (searchVar model)
consoleLog $ "Submit! " <> search_query consoleLog $ "Submit! " <> search_query
Client.search (clientModel model) search_query (clientIface iface) Client.search (clientModel model) search_query (clientIface iface)
update iface (ChangeAndSubmit search_query) model = model { searchTerm = search_query } <# do
_ <- swapMVar (searchVar model) search_query
return $ (passAction iface) OnSubmit
update iface (SearchResult result) model = model <# do update iface (SearchResult result) model = model <# do
consoleLog $ "Received search results!" consoleLog $ "Received search results!"
@ -62,12 +74,13 @@ update iface (PassPostsToSelf search_results) model = model { displayResults = s
update _ NoAction m = noEff m update _ NoAction m = noEff m
view :: Interface a -> Model -> View a view :: Interface a -> Model -> View a
view iface m = form_ view iface m = form_
[ class_ "search_form" [ class_ "search_form"
, action_ "/search" , action_ "/search"
, method_ "GET" , method_ "GET"
, onSubmit $ pass $ OnSubmit $ searchTerm m , onSubmit $ pass $ OnSubmit
] ]
[ input_ [ input_
[ type_ "submit" [ type_ "submit"

View File

@ -2,19 +2,22 @@ module Component.Search.SearchTypes where
import Data.JSString (JSString) import Data.JSString (JSString)
import Network.Http (HttpResult (..)) import Network.Http (HttpResult (..))
import Control.Concurrent.MVar (MVar)
import qualified Network.ClientTypes as Client import qualified Network.ClientTypes as Client
import Network.CatalogPostType (CatalogPost) import Network.CatalogPostType (CatalogPost)
data Action data Action
= SearchChange JSString = SearchChange JSString
| OnSubmit JSString | OnSubmit
| ChangeAndSubmit JSString
| SearchResult (HttpResult [ CatalogPost ]) | SearchResult (HttpResult [ CatalogPost ])
| PassPostsToSelf [ CatalogPost ] -- I think I don't understand something about the update type but I had to add this... | PassPostsToSelf [ CatalogPost ] -- I think I don't understand something about the update type but I had to add this...
| NoAction | NoAction
data Model = Model data Model = Model
{ searchTerm :: JSString { searchTerm :: JSString
, searchVar :: MVar JSString
, clientModel :: Client.Model , clientModel :: Client.Model
, displayResults :: [ CatalogPost ] , displayResults :: [ CatalogPost ]
} deriving Eq } deriving Eq

View File

@ -12,6 +12,7 @@ import qualified Data.Text as T
import Network.URI (uriPath, uriQuery, escapeURIString, unEscapeString, isAllowedInURI) import Network.URI (uriPath, uriQuery, escapeURIString, unEscapeString, isAllowedInURI)
import System.FilePath ((</>)) import System.FilePath ((</>))
import Data.Time.Clock (UTCTime, getCurrentTime) import Data.Time.Clock (UTCTime, getCurrentTime)
import Control.Concurrent.MVar (MVar, newEmptyMVar)
import Data.Aeson (FromJSON) import Data.Aeson (FromJSON)
import Data.JSString (pack, append, unpack) import Data.JSString (pack, append, unpack)
@ -89,10 +90,10 @@ initialActionFromRoute model uri = either (const NoAction) id routing_result
h_thread website board_pathpart board_thread_id _ = GetThread GetThreadArgs {..} h_thread website board_pathpart board_thread_id _ = GetThread GetThreadArgs {..}
h_search :: Maybe Text -> Model -> Action h_search :: Maybe Text -> Model -> Action
h_search Nothing model = GoToTime $ current_time model h_search Nothing m = GoToTime $ current_time m
h_search (Just search_query) model h_search (Just search_query) m
| Search.searchTerm (search_model model) == unescaped_search_query = SearchResults unescaped_search_query | Search.searchTerm (search_model m) == unescaped_search_query = SearchResults unescaped_search_query
| otherwise = (Search.passAction iSearch) $ Search.OnSubmit $ toJSString $ T.unpack search_query | otherwise = (Search.passAction iSearch) $ Search.ChangeAndSubmit unescaped_search_query
where where
unescaped_search_query = toJSString $ unEscapeString $ T.unpack search_query unescaped_search_query = toJSString $ unEscapeString $ T.unpack search_query
@ -104,8 +105,9 @@ initialModel
-> JSString -> JSString
-> URI -> URI
-> UTCTime -> UTCTime
-> MVar JSString
-> Model -> Model
initialModel pgroot client_fetch_count media_root u t = Model initialModel pgroot client_fetch_count media_root u t smv = Model
{ grid_model = Grid.initialModel media_root { grid_model = Grid.initialModel media_root
, client_model = client_model_ , client_model = client_model_
, thread_model = Nothing , thread_model = Nothing
@ -115,6 +117,7 @@ initialModel pgroot client_fetch_count media_root u t = Model
, tc_model = TC.initialModel 0 , tc_model = TC.initialModel 0
, search_model = Search.Model , search_model = Search.Model
{ Search.searchTerm = "" { Search.searchTerm = ""
, Search.searchVar = smv
, Search.clientModel = client_model_ , Search.clientModel = client_model_
, Search.displayResults = [] , Search.displayResults = []
} }
@ -160,11 +163,14 @@ main = do
now <- getCurrentTime now <- getCurrentTime
search_var <- newEmptyMVar
let initial_model = initialModel let initial_model = initialModel
pg_api_root pg_api_root
pg_fetch_count pg_fetch_count
media_root uri media_root uri
now now
search_var
startApp App startApp App
{ model = initial_model { model = initial_model
@ -206,7 +212,17 @@ mainView model = view
(thread_model m) (thread_model m)
search_view :: Maybe Text -> Model -> View Action search_view :: Maybe Text -> Model -> View Action
search_view _ _ = div_ [] [ text "Search results" ] search_view _ m = div_ []
[ div_
[ class_ "page_heading" ]
[ h1_ [] [ text "Search" ]
, time_ [] [ text $ Search.searchTerm $ search_model m ]
]
, Search.view iSearch (search_model m)
, Grid.view iGrid $ (grid_model model)
{ Grid.display_items = (Search.displayResults (search_model m))
}
]
page404 :: View Action page404 :: View Action
page404 = h1_ [] [ text "404 Not Found" ] page404 = h1_ [] [ text "404 Not Found" ]
@ -285,6 +301,7 @@ mainUpdate (SearchAction sa) m =
>>= \sm -> noEff m { search_model = sm } >>= \sm -> noEff m { search_model = sm }
mainUpdate (SearchResults query) m = m { current_uri = new_current_uri } <# do mainUpdate (SearchResults query) m = m { current_uri = new_current_uri } <# do
consoleLog $ "SearchResults new uri: " <> (pack $ show new_current_uri)
pushURI new_current_uri pushURI new_current_uri
return NoAction return NoAction
@ -328,6 +345,6 @@ iSearch :: Search.Interface Action
iSearch = iSearch =
Search.Interface Search.Interface
{ passAction = SearchAction { passAction = SearchAction
, clientIface = iClient (SearchAction . Search.SearchResult) , clientIface = iClient $ SearchAction . Search.SearchResult
, searchResults = SearchResults , searchResults = SearchResults
} }