Skip to content

Commit

Permalink
more better summary
Browse files Browse the repository at this point in the history
clickable tag summary
  • Loading branch information
zachary822 committed Nov 24, 2023
1 parent b9a4869 commit 68724e0
Show file tree
Hide file tree
Showing 8 changed files with 373 additions and 68 deletions.
7 changes: 6 additions & 1 deletion app/Lib/Blaze.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,9 +4,11 @@

module Lib.Blaze where

import Data.String
import Language.Haskell.TH.Quote
import Text.Blaze.Html.Renderer.Utf8 (renderHtml)
import Text.Blaze.Html5 (Html)
import Text.Blaze.Html5 (Attribute, AttributeValue, Html)
import Text.Blaze.Html5 qualified as H
import Text.Blaze.Html5.Attributes qualified as A
import Web.Scotty (ActionM, raw, setHeader)

Expand All @@ -23,3 +25,6 @@ blazeHtml :: Html -> ActionM ()
blazeHtml h = do
setHeader "Content-Type" "text/html; charset=utf-8"
raw . renderHtml $ h

hx :: String -> AttributeValue -> Attribute
hx attr = H.customAttribute (fromString $ "hx-" <> attr)
108 changes: 108 additions & 0 deletions app/Lib/Database.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@ module Lib.Database where

import Control.Monad
import Data.Maybe
import Data.Text (Text)
import Data.Text qualified as T
import Database.MongoDB
import Network.URI
Expand All @@ -25,3 +26,110 @@ getPipe rs uname passwd = do
pipe <- primary rs
_ <- access pipe master admin (auth uname passwd)
return pipe

-- pipelines
postsPipline :: (Val v0, Val v1) => v0 -> v1 -> [Document]
postsPipline limit offset =
[
[ "$facet"
=: [ "data"
=: [ ["$match" =: ["published" =: True]]
, ["$sort" =: ["updated" =: (-1 :: Int)]]
, ["$limit" =: limit]
, ["$skip" =: offset]
, ["$project" =: ["published" =: (0 :: Int)]]
]
, "total"
=: [ ["$match" =: ["published" =: True]]
, ["$count" =: ("total" :: Text)]
]
]
]
,
[ "$project"
=: [ "data" =: (1 :: Int)
, "total" =: ["$first" =: ("$total.total" :: Text)]
]
]
]

postsTagPipline :: (Val v0, Val v1) => Text -> v0 -> v1 -> [Document]
postsTagPipline tag limit offset =
[
[ "$facet"
=: [ "data"
=: [
[ "$match"
=: [ "published" =: True
, "tags" =: ["$in" =: [tag]]
]
]
, ["$sort" =: ["updated" =: (-1 :: Int)]]
, ["$limit" =: limit]
, ["$skip" =: offset]
, ["$project" =: ["published" =: (0 :: Int)]]
]
, "total"
=: [
[ "$match"
=: [ "published" =: True
, "tags" =: ["$in" =: [tag]]
]
]
, ["$count" =: ("total" :: Text)]
]
]
]
,
[ "$project"
=: [ "data" =: (1 :: Int)
, "total" =: ["$first" =: ("$total.total" :: Text)]
]
]
]

summaryPipeline :: [Document]
summaryPipeline =
[
[ "$facet"
=: [ "monthly"
=: [ ["$match" =: ["published" =: True]]
,
[ "$group"
=: [ "_id"
=: [ "year" =: ["$year" =: ("$created" :: Text)]
, "month" =: ["$month" =: ("$created" :: Text)]
]
, "count" =: ["$sum" =: (1 :: Int)]
]
]
,
[ "$project"
=: [ "_id" =: (0 :: Int)
, "year" =: ("$_id.year" :: Text)
, "month" =: ("$_id.month" :: Text)
, "count" =: (1 :: Int)
]
]
]
, "tags"
=: [ ["$match" =: ["published" =: True]]
, ["$unwind" =: ["path" =: ("$tags" :: Text)]]
,
[ "$group"
=: [ "_id" =: ("$tags" :: Text)
, "count" =: ["$sum" =: (1 :: Int)]
]
]
,
[ "$project"
=: [ "_id" =: (0 :: Int)
, "name" =: ("$_id" :: Text)
, "count" =: (1 :: Int)
]
]
, ["$sort" =: ["count" =: (-1 :: Int), "name" =: (-1 :: Int)]]
]
]
]
]
Loading

0 comments on commit 68724e0

Please sign in to comment.