Paste server written in Haskell. Fork of Hpaste, fully freedom and privacy respecting and generally improved. At the time of writing there's an instance at <http://paste.rel4tion.org>.

[[ 🗃 ^aoqmo toothpaste ]] :: [📥 Inbox] [📤 Outbox] [🐤 Followers] [🤝 Collaborators] [🛠 Commits]

Clone

HTTPS: git clone https://vervis.peers.community/repos/aoqmo

SSH: git clone USERNAME@vervis.peers.community:aoqmo

Branches

Tags

hpaste :: src / Hpaste / View /

Report.hs

{-# OPTIONS -Wall -fno-warn-name-shadowing -fno-warn-unused-do-bind #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}

-- | Report view.

module Hpaste.View.Report
  (page,reportFormlet)
  where

import           Hpaste.Types
import           Hpaste.View.Highlight
import           Hpaste.View.Html
import           Hpaste.View.Layout

import           Data.Monoid.Operator        ((++))
import           Data.Text                   (Text)
import           Prelude                     hiding ((++))
import           Text.Blaze.Html5            as H hiding (map)
import qualified Text.Blaze.Html5.Attributes as A
import           Text.Formlet

-- | Render the page page.
page :: Html -> Paste -> Html
page form paste =
  layoutPage $ Page {
    pageTitle = "Report a paste"
  , pageBody = do reporting form; viewPaste paste
  , pageName = "paste"
  }
  
reporting :: Html -> Html
reporting form = do
  lightSection "Report a paste" $ do
    p $ do "Please state any comments regarding the paste:"
    H.form ! A.method "post" $ do
      form

-- | View a paste's details and content.
viewPaste :: Paste -> Html
viewPaste Paste{..} = do
  pasteDetails pasteTitle
  pasteContent pastePaste

-- | List the details of the page in a dark section.
pasteDetails :: Text -> Html
pasteDetails title =
  darkNoTitleSection $ do
    pasteNav
    h2 $ toHtml title
    ul ! aClass "paste-specs" $ do
      detail "Language" $ "Haskell"
      detail "Raw" $ href ("/stepeval/raw" :: Text)
                          ("View raw link" :: Text)
    clear

    where detail title content = do
            li $ do strong (title ++ ":"); content

-- | Individual paste navigation.
pasteNav :: Html
pasteNav =
  H.div ! aClass "paste-nav" $ do
    href ("https://github.com/benmachine/stepeval" :: Text)
         ("Go to stepeval project" :: Text)

-- | Show the paste content with highlighting.
pasteContent :: Text -> Html
pasteContent paste =
  lightNoTitleSection $
    highlightHaskell paste

-- | A formlet for report submission / annotating.
reportFormlet :: ReportFormlet -> (Formlet Text,Html)
reportFormlet ReportFormlet{..} =
  let frm = form $ do
        formletHtml reportSubmit rfParams
        submitInput "submit" "Submit"
  in (reportSubmit,frm)

reportSubmit :: Formlet Text
reportSubmit = req (textInput "report" "Comments" Nothing)
[See repo JSON]