lebd/src/Widget/Card.hs

40 lines
1.4 KiB
Haskell

{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
module Widget.Card ( hCard ) where
import Import
import Database.Esqueleto ( (^.) )
import qualified Database.Esqueleto as E
import Text.Mustache ( substitute )
import Util ( compileMustache )
import qualified Data.Text as T
prettyPgp :: PgpKey -> Text
prettyPgp = T.unwords . T.chunksOf 4 . pgpKeyFingerprint
routeFromPgp :: PgpKey -> Route App
routeFromPgp PgpKey { pgpKeyFingerprint = f } = staticR ["pgp", T.takeEnd 8 f ++ ".asc"]
profileUrl :: Site -> Profile -> Text
profileUrl site = substitute $ T.unpack (siteName site) `compileMustache` siteTemplate site
hCard :: Entity User -> Widget
hCard (Entity userId user) = do
mcurrentRoute <- getCurrentRoute
userProfiles <- handlerToWidget . runDB . E.select . E.from $ \(profile `E.InnerJoin` site) -> do
E.on $ profile ^. ProfileSiteId E.==. site ^. SiteId
E.where_ $ profile ^. ProfileUserId E.==. E.val userId
E.orderBy [E.asc $ site ^. SiteName]
return (site, profile)
pgpKeys <- handlerToWidget . runDB $ map entityVal <$> selectList [PgpKeyUserId ==. userId] []
toWidgetHead [hamlet|
$forall key <- pgpKeys
<link rel="pgpkey" type="application/pgp-keys" href=@{routeFromPgp key}>
|]
$(widgetFile "mf2/h-card")