espial/src/Handler/Add.hs

84 lines
2.5 KiB
Haskell
Raw Normal View History

2019-01-31 02:54:47 +00:00
module Handler.Add where
import Import
import Handler.Archive
import Data.List (nub)
-- View
getAddViewR :: Handler Html
getAddViewR = do
userId <- requireAuthId
murl <- lookupGetParam "url"
mformdb <- runDB (pure . fmap _toBookmarkForm =<< fetchBookmarkByUrl userId murl)
formurl <- bookmarkFormUrl
let renderEl = "addForm" :: Text
2020-07-20 17:43:03 +00:00
popupLayout do
2019-01-31 02:54:47 +00:00
toWidget [whamlet|
<div id="#{ renderEl }">
|]
toWidgetBody [julius|
app.dat.bmark = #{ toJSON (fromMaybe formurl mformdb) };
|]
toWidget [julius|
PS['Main'].renderAddForm('##{rawJS renderEl}')(app.dat.bmark)();
|]
bookmarkFormUrl :: Handler BookmarkForm
bookmarkFormUrl = do
Entity _ user <- requireAuth
2020-06-15 14:45:33 +00:00
url <- lookupGetParam "url" >>= pure . fromMaybe ""
title <- lookupGetParam "title"
description <- lookupGetParam "description" >>= pure . fmap Textarea
tags <- lookupGetParam "tags"
private <- lookupGetParam "private" >>= pure . fmap parseChk <&> (<|> Just (userPrivateDefault user))
toread <- lookupGetParam "toread" >>= pure . fmap parseChk
pure $
BookmarkForm
{ _url = url
, _title = title
, _description = description
, _tags = tags
, _private = private
, _toread = toread
, _bid = Nothing
, _slug = Nothing
, _selected = Nothing
, _time = Nothing
, _archiveUrl = Nothing
}
2019-01-31 02:54:47 +00:00
where
parseChk s = s == "yes" || s == "on"
-- API
postAddR :: Handler ()
postAddR = do
bookmarkForm <- requireCheckJsonBody
_handleFormSuccess bookmarkForm >>= \case
(Created, bid) -> sendStatusJSON created201 bid
(Updated, _) -> sendResponseStatus noContent204 ()
_handleFormSuccess :: BookmarkForm -> Handler (UpsertResult, Key Bookmark)
_handleFormSuccess bookmarkForm = do
(userId, user) <- requireAuthPair
bm <- liftIO $ _toBookmark userId bookmarkForm
2019-09-15 23:13:07 +00:00
(res, kbid) <- runDB (upsertBookmark userId mkbid bm tags)
2019-01-31 02:54:47 +00:00
whenM (shouldArchiveBookmark user kbid) $
void $ async (archiveBookmarkUrl kbid (unpack (bookmarkHref bm)))
pure (res, kbid)
where
mkbid = BookmarkKey <$> _bid bookmarkForm
tags = maybe [] (nub . words) (_tags bookmarkForm)
postLookupTitleR :: Handler ()
postLookupTitleR = do
void requireAuthId
bookmarkForm <- (requireCheckJsonBody :: Handler BookmarkForm)
fetchPageTitle (unpack (_url bookmarkForm)) >>= \case
Left _ -> sendResponseStatus noContent204 ()
Right title -> sendResponseStatus ok200 title