{-# LANGUAGE FlexibleContexts, TypeFamilies, QuasiQuotes, OverloadedStrings #-} module Clckwrks.Authenticate.Page.ViewUsers where import Clckwrks.Admin.Template (template) import Clckwrks.Monad import Clckwrks.URL (ClckURL(..)) import Clckwrks.Authenticate.Monad () import Clckwrks.ProfileData.URL(ProfileDataURL(..)) import Data.Maybe (maybe) import Data.Foldable (toList) import qualified Data.Text as Text import Happstack.Server (Response, ServerPartT, ok, toResponse) import Happstack.Authenticate.Core (Email(..), GetUsers(..), User(..), UserId(..), Username(..)) import Language.Haskell.HSX.QQ (hsx) import Web.Plugins.Core (Plugin(..), getPluginState) import Web.Routes (showURL) viewUsers :: ClckT ClckURL (ServerPartT IO) Response viewUsers = do us <- query GetUsers template "View Users" () $ [hsx|

Users

<% mapM mkRow (toList us) %>
UserIdUsernameEmail
|] where mkRow u = do epdf <- showURL (Profile (EditProfileDataFor (_userId u))) [hsx| <% show $ _unUserId $ _userId u %><% _unUsername $ _username u %><% maybe (Text.empty) _unEmail (_email u) %> |]