get note sql

This commit is contained in:
me 2024-12-17 10:46:59 +02:00
parent fa05ae4bf2
commit bc4039c7fd
2 changed files with 36 additions and 14 deletions

View file

@ -1,6 +1,7 @@
-- | Database interaction -- | Database interaction
module DB where module DB where
import Data.Maybe (listToMaybe)
import GHC.Stack (HasCallStack) import GHC.Stack (HasCallStack)
import Data.Text qualified as T import Data.Text qualified as T
import Database.Sqlite.Easy qualified as DB import Database.Sqlite.Easy qualified as DB
@ -13,6 +14,7 @@ import Fedi
data DB data DB
= DB = DB
{ getNotes :: IO [Note] { getNotes :: IO [Note]
, getNote :: DB.Int64 -> IO (Maybe Note)
, insertNote :: NoteEntry -> IO NoteId , insertNote :: NoteEntry -> IO NoteId
} }
@ -36,6 +38,8 @@ mkDB connstr details = do
pure DB pure DB
{ getNotes = { getNotes =
DB.withPool pool (getNotesFromDb $ actorUrl details) DB.withPool pool (getNotesFromDb $ actorUrl details)
, getNote =
\noteid -> DB.withPool pool (getNoteFromDb noteid $ actorUrl details)
, insertNote = , insertNote =
\note -> DB.withPool pool (insertNoteToDb (actorUrl details) note) \note -> DB.withPool pool (insertNoteToDb (actorUrl details) note)
} }
@ -84,6 +88,11 @@ getNotesFromDb :: Url -> DB.SQLite [Note]
getNotesFromDb url = getNotesFromDb url =
map decodeNoteRow <$> uncurry DB.runWith (getNotesSQL url) map decodeNoteRow <$> uncurry DB.runWith (getNotesSQL url)
getNoteFromDb :: DB.Int64 -> Url -> DB.SQLite (Maybe Note)
getNoteFromDb noteid url = do
n <- map decodeNoteRow <$> uncurry DB.runWith (getNoteSQL noteid url)
pure (listToMaybe n)
insertNoteToDb :: Url -> NoteEntry -> DB.SQLite NoteId insertNoteToDb :: Url -> NoteEntry -> DB.SQLite NoteId
insertNoteToDb actor note = do insertNoteToDb actor note = do
[n] <- map decodeNoteIdRow <$> uncurry DB.runWith (insertNoteSQL actor note) [n] <- map decodeNoteIdRow <$> uncurry DB.runWith (insertNoteSQL actor note)
@ -103,11 +112,30 @@ getNotesSQL url =
inReplyTo, inReplyTo,
url url
FROM note FROM note
WHERE inReplyTo IS NULL
ORDER BY published DESC ORDER BY published DESC
|] |]
, [DB.SQLText $ T.pack url] , [DB.SQLText $ T.pack url]
) )
getNoteSQL :: DB.Int64 -> Url -> (DB.SQL, [DB.SQLData])
getNoteSQL noteid url =
( [r|
SELECT
? || '/notes/' || id,
published,
actor,
content,
name,
inReplyTo,
url
FROM note
WHERE note.id = ?
ORDER BY published DESC
|]
, [DB.SQLText $ T.pack url, DB.SQLInteger noteid]
)
insertNoteSQL :: Url -> NoteEntry -> (DB.SQL, [DB.SQLData]) insertNoteSQL :: Url -> NoteEntry -> (DB.SQL, [DB.SQLData])
insertNoteSQL actor note = insertNoteSQL actor note =
( [r| ( [r|

View file

@ -1,5 +1,6 @@
module Routes where module Routes where
import Data.Maybe (maybeToList)
import Data.String (fromString) import Data.String (fromString)
import Data.Aeson qualified as A import Data.Aeson qualified as A
import Web.Twain qualified as Twain import Web.Twain qualified as Twain
@ -42,25 +43,18 @@ routes db detailsFile =
, -- Match Note object , -- Match Note object
Twain.get (Fedi.matchNote $ unsafePerformIO $ fetchUserDetails detailsFile) do Twain.get (Fedi.matchNote $ unsafePerformIO $ fetchUserDetails detailsFile) do
details <- liftIO $ fetchUserDetails detailsFile details <- liftIO $ fetchUserDetails detailsFile
notes <- liftIO db.getNotes noteId <- Twain.param "note_id"
mnote <- liftIO $ db.getNote noteId
request <- Twain.request request <- Twain.request
if Fedi.checkContentTypeAccept request if Fedi.checkContentTypeAccept request
then do then do
Fedi.handleNote details notes Fedi.handleNote details (maybeToList mnote)
else do else do
noteId <- Twain.param "note_id" case mnote of
let Nothing -> Twain.next
noteUrl = Just thenote ->
"https://" Twain.send $ Twain.html $ H.renderBS $ actorPage details [thenote]
<> details.domain
<> "/"
<> details.username
<> "/notes/"
<> noteId
thenote = filter (\note -> note.id == noteUrl) notes
Twain.send $ Twain.html $ H.renderBS $ actorPage details thenote
, -- Match webfinger , -- Match webfinger
Twain.get Fedi.matchWebfinger do Twain.get Fedi.matchWebfinger do