eidolon/Handler/Search.hs

68 lines
2.5 KiB
Haskell
Raw Normal View History

2015-10-18 02:59:43 +00:00
-- eidolon -- A simple gallery in Haskell and Yesod
-- Copyright (C) 2015 Amedeo Molnár
--
-- This program is free software: you can redistribute it and/or modify
-- it under the terms of the GNU Affero General Public License as published
-- by the Free Software Foundation, either version 3 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 Affero General Public License for more details.
--
-- You should have received a copy of the GNU Affero General Public License
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
2017-10-20 16:49:37 +00:00
module Handler.Search where
2017-10-20 16:49:37 +00:00
import Import
2017-10-20 16:49:37 +00:00
import qualified Data.Text as T
import Data.Maybe (fromJust)
2017-10-21 17:10:53 +00:00
import Data.List (sortBy, nub)
2016-08-30 12:22:00 +00:00
2017-10-21 19:18:59 +00:00
import Text.Fuzzy (test)
2017-10-20 16:49:37 +00:00
import Database.Persist.Sql (rawSql)
import System.FilePath (splitDirectories)
getSearchR :: Handler Html
getSearchR = do
((res, widget), _) <- runFormGet $ renderBootstrap3 BootstrapBasicForm $
searchForm
case res of
FormSuccess query -> do
2017-10-21 14:11:56 +00:00
mediumList <- runDB $ do
2017-10-21 14:20:38 +00:00
a <- rawSql "select ?? from medium where ? % any(string_to_array(title, ' '))"
2017-10-21 13:53:43 +00:00
[PersistText query]
2017-10-21 14:20:38 +00:00
b <- rawSql "select ?? from medium where ? % any(string_to_array(description, ' '))"
2017-10-21 13:53:43 +00:00
[PersistText query]
2017-10-21 19:18:59 +00:00
return $ nub $ sortBy (\sa sb -> compare
2017-10-21 14:11:56 +00:00
(T.unpack $ mediumTitle $ entityVal sa)
(T.unpack $ mediumTitle $ entityVal sb))
$ a ++ b
2017-10-20 16:49:37 +00:00
userList <- runDB $
rawSql "select ?? from \"user\" where name % ?" [PersistText query]
albumList <- runDB $
rawSql "select ?? from album where title % ?" [PersistText query]
2017-10-21 19:18:59 +00:00
tagList <- runDB $ do
media <- selectList [] [Asc MediumTitle]
let tags = sortBy
(\sa sb -> compare sa sb)
(nub (concatMap mediumTags (map entityVal media)))
ret = filter (\a -> query `test` a) tags
return ret
2017-10-20 16:49:37 +00:00
let allEmpty = null mediumList && null userList && null albumList
defaultLayout $ do
setTitle $ toHtml $ "Eidolon :: Search results for " ++ (T.unpack query)
$(widgetFile "result")
_ ->
defaultLayout $ do
setTitle "Eidolon :: Search"
$(widgetFile "search")
searchForm :: AForm Handler T.Text
searchForm = areq (searchField True) "Search" Nothing