2016-03-15 15:35:35 +03:00
|
|
|
|
{-# LANGUAGE
|
|
|
|
|
QuasiQuotes,
|
|
|
|
|
OverloadedStrings,
|
|
|
|
|
FlexibleContexts,
|
|
|
|
|
NoImplicitPrelude
|
|
|
|
|
#-}
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
module View
|
|
|
|
|
(
|
2016-08-17 11:18:57 +03:00
|
|
|
|
getJS,
|
|
|
|
|
getCSS,
|
|
|
|
|
|
2016-03-15 15:35:35 +03:00
|
|
|
|
-- * Pages
|
|
|
|
|
renderRoot,
|
2016-04-07 22:14:08 +03:00
|
|
|
|
renderAdmin,
|
2016-04-15 14:14:01 +03:00
|
|
|
|
renderEdits,
|
2016-03-23 18:28:03 +03:00
|
|
|
|
renderHaskellRoot,
|
2016-03-15 15:35:35 +03:00
|
|
|
|
renderDonate,
|
2016-03-19 02:40:00 +03:00
|
|
|
|
renderCategoryPage,
|
2016-05-05 23:11:08 +03:00
|
|
|
|
renderStaticMd,
|
2016-05-01 23:17:55 +03:00
|
|
|
|
renderSearchResults,
|
2016-03-15 15:35:35 +03:00
|
|
|
|
|
|
|
|
|
-- * Methods
|
|
|
|
|
-- ** Categories
|
|
|
|
|
renderCategoryList,
|
|
|
|
|
renderCategory,
|
2016-05-05 16:50:10 +03:00
|
|
|
|
renderCategoryInfo,
|
2016-03-15 15:35:35 +03:00
|
|
|
|
renderCategoryNotes,
|
|
|
|
|
-- ** Items
|
|
|
|
|
renderItem,
|
|
|
|
|
renderItemInfo,
|
|
|
|
|
renderItemDescription,
|
2016-03-17 02:52:40 +03:00
|
|
|
|
renderItemEcosystem,
|
2016-03-15 15:35:35 +03:00
|
|
|
|
renderItemTraits,
|
|
|
|
|
renderItemNotes,
|
|
|
|
|
-- ** Traits
|
|
|
|
|
renderTrait,
|
|
|
|
|
|
2016-03-19 21:36:21 +03:00
|
|
|
|
-- * Rendering for feeds
|
|
|
|
|
renderItemForFeed,
|
|
|
|
|
|
2016-03-15 15:35:35 +03:00
|
|
|
|
-- * Miscellaneous
|
|
|
|
|
getItemHue,
|
|
|
|
|
)
|
|
|
|
|
where
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
import BasePrelude hiding (Category)
|
|
|
|
|
-- Lenses
|
|
|
|
|
import Lens.Micro.Platform hiding ((&))
|
|
|
|
|
-- Monads and monad transformers
|
|
|
|
|
import Control.Monad.IO.Class
|
2016-03-22 01:17:53 +03:00
|
|
|
|
import Control.Monad.Reader
|
2016-08-17 11:18:57 +03:00
|
|
|
|
-- Lists
|
|
|
|
|
import Data.List.Split
|
2016-03-15 15:35:35 +03:00
|
|
|
|
-- Containers
|
|
|
|
|
import qualified Data.Map as M
|
2016-04-16 02:02:43 +03:00
|
|
|
|
import Data.Tree
|
2016-03-15 15:35:35 +03:00
|
|
|
|
-- Text
|
2016-06-12 22:35:13 +03:00
|
|
|
|
import qualified Data.Text.All as T
|
2016-08-19 04:07:45 +03:00
|
|
|
|
import qualified Data.Text.Lazy.All as TL
|
2016-06-12 22:35:13 +03:00
|
|
|
|
import Data.Text.All (Text)
|
2016-03-15 15:35:35 +03:00
|
|
|
|
import NeatInterpolation
|
|
|
|
|
-- Web
|
|
|
|
|
import Lucid hiding (for_)
|
2016-08-17 11:18:57 +03:00
|
|
|
|
-- Files
|
|
|
|
|
import System.FilePath
|
|
|
|
|
import qualified System.FilePath.Find as F
|
2016-05-08 16:29:07 +03:00
|
|
|
|
-- Network
|
|
|
|
|
import Data.IP
|
2016-04-07 22:14:08 +03:00
|
|
|
|
-- Time
|
2016-05-04 21:03:23 +03:00
|
|
|
|
import Data.Time
|
2016-04-07 22:14:08 +03:00
|
|
|
|
import Data.Time.Format.Human
|
2016-04-16 02:02:43 +03:00
|
|
|
|
-- Markdown
|
2016-07-24 13:12:17 +03:00
|
|
|
|
import qualified CMark as MD
|
2016-08-17 11:18:57 +03:00
|
|
|
|
-- Mustache (templates)
|
|
|
|
|
import Text.Mustache.Plus
|
|
|
|
|
import qualified Data.Aeson as A
|
|
|
|
|
import qualified Data.Aeson.Encode.Pretty as A
|
|
|
|
|
import qualified Data.ByteString.Lazy.Char8 as BS
|
|
|
|
|
import qualified Data.Semigroup as Semigroup
|
|
|
|
|
import qualified Data.List.NonEmpty as NonEmpty
|
|
|
|
|
import Text.Megaparsec
|
|
|
|
|
import Text.Megaparsec.Text
|
2016-03-15 15:35:35 +03:00
|
|
|
|
|
|
|
|
|
-- Local
|
2016-03-22 01:17:53 +03:00
|
|
|
|
import Config
|
2016-03-15 15:35:35 +03:00
|
|
|
|
import Types
|
|
|
|
|
import Utils
|
|
|
|
|
import JS (JS(..), JQuerySelector)
|
|
|
|
|
import qualified JS
|
|
|
|
|
import Markdown
|
2016-05-01 16:28:10 +03:00
|
|
|
|
import Cache
|
2016-03-15 15:35:35 +03:00
|
|
|
|
|
|
|
|
|
|
|
|
|
|
{- Note [autosize]
|
|
|
|
|
~~~~~~~~~~~~~~~~~~
|
|
|
|
|
|
2016-10-20 18:54:20 +03:00
|
|
|
|
All textareas on the site are autosized – i.e. they grow when the user is
|
|
|
|
|
typing. This is done by the autosize.js plugin, which is called on page load:
|
2016-03-15 15:35:35 +03:00
|
|
|
|
|
|
|
|
|
autosize($('textarea'));
|
|
|
|
|
|
2016-10-20 18:54:20 +03:00
|
|
|
|
A slight problem is that it doesn't compute the height of hidden elements
|
|
|
|
|
correctly – thus, when something is shown and it happens to be a textarea or
|
|
|
|
|
contain a textarea, we have to call autosize again. This is done in
|
|
|
|
|
'JS.switchSection'. So far there are no textboxes that are shown *without*
|
|
|
|
|
switchSection being involved, and so there's no need to watch for elements
|
|
|
|
|
being added to the DOM.
|
2016-03-15 15:35:35 +03:00
|
|
|
|
|
2016-10-20 18:54:20 +03:00
|
|
|
|
It would be nicer if we could watch for elements becoming visible without
|
|
|
|
|
having to modify switchSection, but there doesn't seem to be an easy way to
|
|
|
|
|
do this – MutationObserver doesn't let us find out when something becomes
|
|
|
|
|
visible (i.e. when its clientHeight stops being 0).
|
2016-03-15 15:35:35 +03:00
|
|
|
|
|
|
|
|
|
In switchSection we use
|
|
|
|
|
|
|
|
|
|
autosize($('textarea'));
|
|
|
|
|
autosize.update($('textarea'));
|
|
|
|
|
|
|
|
|
|
instead of simple
|
|
|
|
|
|
|
|
|
|
autosize.update($('textarea'));
|
|
|
|
|
|
2016-10-20 18:54:20 +03:00
|
|
|
|
– this is done because the textarea could have appeared after the original
|
|
|
|
|
`autosize($('textarea'));` was called on page load (which could happen if an
|
|
|
|
|
item was added, for instance).
|
2016-03-15 15:35:35 +03:00
|
|
|
|
|
|
|
|
|
-}
|
|
|
|
|
|
2016-03-27 02:34:07 +03:00
|
|
|
|
{- Note [show-hide]
|
|
|
|
|
~~~~~~~~~~~~~~~~~~~
|
|
|
|
|
|
2016-10-20 18:54:20 +03:00
|
|
|
|
A lot of things (notes, etc) can be expanded/collapsed by pressing a
|
|
|
|
|
button. Similarly, pressing “edit” replaces rendered text with a textbox, or
|
|
|
|
|
adds buttons to pros/cons. All this is done with sections and show/hide.
|
2016-03-27 02:34:07 +03:00
|
|
|
|
|
2016-10-20 18:54:20 +03:00
|
|
|
|
A section is something that can be shown or hidden. You define a section by
|
|
|
|
|
using 'section' (which creates a <div>) or 'sectionSpan' (which creates a
|
|
|
|
|
<span>).
|
2016-03-27 02:34:07 +03:00
|
|
|
|
|
|
|
|
|
section "normal" [shown, noScriptShown] $ do
|
|
|
|
|
renderText
|
|
|
|
|
...
|
|
|
|
|
|
|
|
|
|
section "editing" [] $ do
|
|
|
|
|
renderEditbox
|
|
|
|
|
...
|
|
|
|
|
|
2016-10-20 18:54:20 +03:00
|
|
|
|
You can even give 2 names to a section – e.g. "normal editing" if you want
|
|
|
|
|
the section be visible both in “normal” mode and in “editing” mode.
|
2016-04-11 23:31:30 +03:00
|
|
|
|
|
2016-10-20 18:54:20 +03:00
|
|
|
|
The list parameter is used to add attributes to the section. 'shown' is an
|
|
|
|
|
attribute that means that the section is normally visible; 'noScriptShown'
|
|
|
|
|
means that the section will be visible when Javascipt is disabled. Sections
|
|
|
|
|
without either attribute will be hidden. (Usually 'shown' and 'noScriptShown'
|
|
|
|
|
go together, but not always.)
|
2016-03-27 02:34:07 +03:00
|
|
|
|
|
2016-10-20 18:54:20 +03:00
|
|
|
|
When several sections are in the same container (e.g. a <div>), you can
|
|
|
|
|
toggle between them with 'JS.switchSection', which shows the section (or
|
|
|
|
|
several sections) with given name, and hides all sections with other
|
|
|
|
|
names. The elements that aren't sections are not affected.
|
2016-03-27 02:34:07 +03:00
|
|
|
|
|
2016-10-20 18:54:20 +03:00
|
|
|
|
Also, there's another function available – 'JS.switchSectionEverywhere' –
|
|
|
|
|
that switches sections everywhere inside the container, not only among
|
|
|
|
|
container's direct children. It's useful when you have something like a list
|
|
|
|
|
of pros/cons and you want to switch them all into the “editable” state.
|
2016-03-27 02:34:07 +03:00
|
|
|
|
|
2016-04-11 23:31:30 +03:00
|
|
|
|
////////////////////////////////////
|
|
|
|
|
|
2016-03-27 02:34:07 +03:00
|
|
|
|
And now, here's how it's all implemented.
|
|
|
|
|
|
2016-10-20 18:54:20 +03:00
|
|
|
|
In 'wrapPage' there's a piece of CSS wrapped in <noscript> that hides
|
|
|
|
|
everything except for 'noScriptShown' things:
|
2016-03-27 02:34:07 +03:00
|
|
|
|
|
|
|
|
|
.section:not(.noscript-shown) {display:none;}
|
|
|
|
|
|
2016-10-20 18:54:20 +03:00
|
|
|
|
There's also a piece of Javascript that, when executed, will change it to the
|
|
|
|
|
following CSS:
|
2016-03-27 02:34:07 +03:00
|
|
|
|
|
|
|
|
|
.section:not(.shown) {display:none;}
|
|
|
|
|
|
2016-10-20 18:54:20 +03:00
|
|
|
|
So, if Javascript is disabled we hide all sections except for those that have
|
|
|
|
|
the 'noScriptShown' attribute, and if it's enabled we hide all sections
|
|
|
|
|
except for those that have the 'shown' attribute.
|
2016-03-27 02:34:07 +03:00
|
|
|
|
|
2016-10-20 18:54:20 +03:00
|
|
|
|
After that switching sections is simply done by adding/removing the “shown”
|
|
|
|
|
class. (Note that we don't have to choose between “noscript-shown” and
|
|
|
|
|
“shown” because switching sections is *only* possible if Javascript is
|
|
|
|
|
enabled, and in this case the relevant tag will always be “shown” and not
|
|
|
|
|
“noscript-shown”.)
|
2016-03-27 02:34:07 +03:00
|
|
|
|
|
|
|
|
|
-}
|
|
|
|
|
|
2016-11-27 14:45:38 +03:00
|
|
|
|
renderSubtitle :: (MonadReader Config m) => HtmlT m ()
|
2016-07-10 23:34:13 +03:00
|
|
|
|
renderSubtitle =
|
2016-08-25 15:05:54 +03:00
|
|
|
|
div_ [class_ "subtitle"] $ do
|
|
|
|
|
"alpha version • don't post on Reddit yet"
|
|
|
|
|
lift (asks _discussLink) >>= \case
|
|
|
|
|
Nothing -> return ()
|
|
|
|
|
Just l -> " • " >> mkLink "discuss the site" l
|
2016-07-10 23:34:13 +03:00
|
|
|
|
|
2016-07-25 19:47:49 +03:00
|
|
|
|
renderRoot :: (MonadIO m, MonadReader Config m) => HtmlT m ()
|
2016-03-23 18:28:03 +03:00
|
|
|
|
renderRoot = do
|
|
|
|
|
wrapPage "Aelve Guide" $ do
|
|
|
|
|
h1_ "Aelve Guide"
|
2016-07-10 23:34:13 +03:00
|
|
|
|
renderSubtitle
|
2016-05-03 03:27:30 +03:00
|
|
|
|
h2_ (mkLink "Haskell" "/haskell")
|
2016-03-23 18:28:03 +03:00
|
|
|
|
|
2016-04-07 22:14:08 +03:00
|
|
|
|
-- TODO: show a “category not found” page
|
|
|
|
|
|
2016-07-25 19:47:49 +03:00
|
|
|
|
renderAdmin :: (MonadIO m) => GlobalState -> HtmlT m ()
|
2016-05-04 21:03:23 +03:00
|
|
|
|
renderAdmin globalState = do
|
2016-04-08 18:05:52 +03:00
|
|
|
|
head_ $ do
|
|
|
|
|
includeJS "/js.js"
|
2016-05-27 17:19:29 +03:00
|
|
|
|
includeJS "/jquery.js"
|
2016-05-08 16:29:07 +03:00
|
|
|
|
includeJS "/sorttable.js"
|
2016-04-09 03:36:38 +03:00
|
|
|
|
includeCSS "/markup.css"
|
2016-04-14 01:56:13 +03:00
|
|
|
|
includeCSS "/admin.css"
|
2016-04-16 23:06:59 +03:00
|
|
|
|
includeCSS "/loader.css"
|
2016-04-13 18:38:35 +03:00
|
|
|
|
title_ "admin – Aelve Guide"
|
2016-04-08 18:05:52 +03:00
|
|
|
|
meta_ [name_ "viewport",
|
|
|
|
|
content_ "width=device-width, initial-scale=1.0, user-scalable=yes"]
|
|
|
|
|
|
|
|
|
|
body_ $ do
|
2016-04-16 23:06:59 +03:00
|
|
|
|
script_ $ fromJS $ JS.createAjaxIndicator ()
|
2016-04-16 00:06:34 +03:00
|
|
|
|
h1_ "Miscellaneous"
|
|
|
|
|
buttonUid <- randomLongUid
|
|
|
|
|
button "Create checkpoint" [uid_ buttonUid] $
|
|
|
|
|
JS.createCheckpoint [JS.selectUid buttonUid]
|
2016-05-14 01:33:14 +03:00
|
|
|
|
div_ [id_ "stats"] $
|
2016-05-04 21:03:23 +03:00
|
|
|
|
renderStats globalState (globalState ^. actions)
|
2016-05-14 01:33:14 +03:00
|
|
|
|
div_ [id_ "edits"] $
|
2016-05-04 21:03:23 +03:00
|
|
|
|
renderEdits globalState (map (,Nothing) (globalState ^. pendingEdits))
|
|
|
|
|
|
|
|
|
|
renderStats
|
|
|
|
|
:: (MonadIO m)
|
|
|
|
|
=> GlobalState
|
|
|
|
|
-> [(Action, ActionDetails)]
|
|
|
|
|
-> HtmlT m ()
|
|
|
|
|
renderStats globalState acts = do
|
2016-05-14 01:33:14 +03:00
|
|
|
|
h1_ "Statistics"
|
2016-05-04 21:03:23 +03:00
|
|
|
|
p_ "All information is for last 31 days."
|
|
|
|
|
now <- liftIO getCurrentTime
|
|
|
|
|
let thisMonth (_, d) = diffUTCTime now (actionDate d) <= 31*86400
|
|
|
|
|
acts' = takeWhile thisMonth acts
|
|
|
|
|
p_ $ do
|
|
|
|
|
"Main page visits: "
|
|
|
|
|
strong_ $ toHtml $ show $ length [() | (Action'MainPageVisit, _) <- acts']
|
|
|
|
|
". "
|
|
|
|
|
"Edits: "
|
|
|
|
|
strong_ $ toHtml $ show $ length [() | (Action'Edit _, _) <- acts']
|
|
|
|
|
". "
|
|
|
|
|
"Unique visitors: "
|
|
|
|
|
strong_ $ toHtml $ show $ length $ ordNub $ map (actionIP.snd) acts'
|
|
|
|
|
"."
|
|
|
|
|
let allCategories = globalState^.categories ++
|
|
|
|
|
globalState^.categoriesDeleted
|
|
|
|
|
-- TODO: move this somewhere else (it's also used in renderEdit)
|
|
|
|
|
let findCategory catId = fromMaybe err (find (hasUid catId) allCategories)
|
|
|
|
|
where
|
|
|
|
|
err = error ("renderStats: couldn't find category with uid = " ++
|
|
|
|
|
T.unpack (uidToText catId))
|
2016-05-08 16:29:07 +03:00
|
|
|
|
table_ [class_ "sortable"] $ do
|
2016-05-04 21:03:23 +03:00
|
|
|
|
thead_ $ tr_ $ do
|
2016-05-08 16:29:07 +03:00
|
|
|
|
th_ [class_ "sorttable_nosort"] "Category"
|
|
|
|
|
th_ "Visits"
|
|
|
|
|
th_ "Unique visitors"
|
|
|
|
|
tbody_ $ do
|
|
|
|
|
let rawVisits :: [(Uid Category, Maybe IP)]
|
|
|
|
|
rawVisits = [(catId, actionIP d) |
|
|
|
|
|
(Action'CategoryVisit catId, d) <- acts']
|
|
|
|
|
let visits :: [(Uid Category, (Int, Int))]
|
|
|
|
|
visits = map (over _2 (length &&& length.ordNub)) .
|
|
|
|
|
map (fst.head &&& map snd) .
|
|
|
|
|
groupWith fst
|
|
|
|
|
$ rawVisits
|
|
|
|
|
for_ (reverse $ sortWith (fst.snd) visits) $ \(catId, (n, u)) -> do
|
|
|
|
|
tr_ $ do
|
|
|
|
|
td_ (toHtml (findCategory catId ^. title))
|
|
|
|
|
td_ (toHtml (show n))
|
|
|
|
|
td_ (toHtml (show u))
|
|
|
|
|
table_ [class_ "sortable"] $ do
|
|
|
|
|
thead_ $ tr_ $ do
|
|
|
|
|
th_ [class_ "sorttable_nosort"] "Search"
|
|
|
|
|
th_ "Repetitions"
|
|
|
|
|
tbody_ $ do
|
|
|
|
|
let searches = map (head &&& length) . group $
|
|
|
|
|
[s | (Action'Search s, _) <- acts']
|
|
|
|
|
for_ (reverse $ sortWith snd searches) $ \(s, n) -> do
|
|
|
|
|
tr_ $ do
|
|
|
|
|
td_ (toHtml s)
|
|
|
|
|
td_ (toHtml (show n))
|
|
|
|
|
table_ [class_ "sortable"] $ do
|
2016-05-04 21:03:23 +03:00
|
|
|
|
thead_ $ tr_ $ do
|
2016-05-08 16:29:07 +03:00
|
|
|
|
th_ [class_ "sorttable_nosort"] "Referrer"
|
|
|
|
|
th_ "Visitors"
|
|
|
|
|
th_ "Unique visitors"
|
|
|
|
|
tbody_ $ do
|
|
|
|
|
let rawVisits :: [(Url, Maybe IP)]
|
|
|
|
|
rawVisits = [(r, actionIP d) |
|
|
|
|
|
(_, d) <- acts',
|
|
|
|
|
Just (ExternalReferrer r) <- [actionReferrer d]]
|
|
|
|
|
let visits :: [(Url, (Int, Int))]
|
|
|
|
|
visits = map (over _2 (length &&& length.ordNub)) .
|
|
|
|
|
map (fst.head &&& map snd) .
|
|
|
|
|
groupWith fst
|
|
|
|
|
$ rawVisits
|
|
|
|
|
for_ (reverse $ sortWith (fst.snd) visits) $ \(r, (n, u)) -> do
|
|
|
|
|
tr_ $ do
|
|
|
|
|
td_ (toHtml r)
|
|
|
|
|
td_ (toHtml (show n))
|
|
|
|
|
td_ (toHtml (show u))
|
2016-05-04 21:03:23 +03:00
|
|
|
|
table_ $ do
|
|
|
|
|
thead_ $ tr_ $ do
|
2016-05-08 16:29:07 +03:00
|
|
|
|
th_ "Action"
|
|
|
|
|
th_ "Date"
|
|
|
|
|
th_ "IP"
|
|
|
|
|
tbody_ $ do
|
|
|
|
|
-- acts, not acts' (what if there were less than 10 actions in the last
|
|
|
|
|
-- month?)
|
|
|
|
|
for_ (take 10 acts) $ \(a, d) -> tr_ $ do
|
|
|
|
|
td_ $ case a of
|
|
|
|
|
Action'Edit _ -> "Edit"
|
|
|
|
|
Action'MainPageVisit -> "Main page visit"
|
|
|
|
|
Action'CategoryVisit _ -> "Category visit"
|
|
|
|
|
Action'Search _ -> "Search"
|
|
|
|
|
td_ $ toHtml =<< liftIO (humanReadableTime (actionDate d))
|
|
|
|
|
td_ $ case actionIP d of
|
|
|
|
|
Nothing -> "<unknown IP>"
|
|
|
|
|
Just ip -> toHtml (show ip)
|
2016-04-07 22:14:08 +03:00
|
|
|
|
|
2016-04-09 00:50:13 +03:00
|
|
|
|
-- TODO: when showing Edit'DeleteCategory, show the amount of items in that
|
|
|
|
|
-- category and titles of items themselves
|
|
|
|
|
|
2016-04-15 14:14:01 +03:00
|
|
|
|
-- | Group edits by IP and render them
|
|
|
|
|
renderEdits
|
2016-07-25 19:47:49 +03:00
|
|
|
|
:: (MonadIO m)
|
2016-04-15 14:14:01 +03:00
|
|
|
|
=> GlobalState
|
|
|
|
|
-> [((Edit, EditDetails), Maybe String)]
|
|
|
|
|
-> HtmlT m ()
|
|
|
|
|
renderEdits globalState edits = do
|
2016-05-14 01:33:14 +03:00
|
|
|
|
let getIP = editIP . snd . fst
|
|
|
|
|
-- Unlike 'groupWith', “groupBy . equating” doesn't sort the input.
|
|
|
|
|
let editBlocks = groupBy (equating getIP) edits
|
|
|
|
|
let ipNum = length $ groupWith getIP edits
|
|
|
|
|
h1_ $ toHtml $
|
2016-06-12 22:35:13 +03:00
|
|
|
|
T.format "Pending edits (IPs: {}, blocks: {})" (ipNum, length editBlocks)
|
2016-04-15 14:14:01 +03:00
|
|
|
|
for_ editBlocks $ \editBlock -> div_ $ do
|
|
|
|
|
blockNode <- thisNode
|
|
|
|
|
h2_ $ do
|
|
|
|
|
case editIP (editBlock ^?! _head._1._2) of
|
|
|
|
|
Nothing -> "<unknown IP>"
|
|
|
|
|
Just ip -> toHtml (show ip)
|
|
|
|
|
emptySpan "1em"
|
|
|
|
|
textButton "accept all" $
|
|
|
|
|
JS.acceptBlock (editId (editBlock ^?! _head._1._2),
|
|
|
|
|
editId (editBlock ^?! _last._1._2),
|
|
|
|
|
blockNode)
|
|
|
|
|
emptySpan "0.5em"
|
|
|
|
|
textButton "undo all" $
|
|
|
|
|
JS.undoBlock (editId (editBlock ^?! _head._1._2),
|
|
|
|
|
editId (editBlock ^?! _last._1._2),
|
|
|
|
|
blockNode)
|
2016-05-25 23:57:12 +03:00
|
|
|
|
for_ editBlock $ \((edit, EditDetails{..}), mbErr) ->
|
|
|
|
|
div_ [class_ "edit"] $ do
|
2016-04-15 14:14:01 +03:00
|
|
|
|
editNode <- thisNode
|
2016-05-25 23:57:12 +03:00
|
|
|
|
p_ [class_ "edit-info"] $ do
|
2016-04-15 14:14:01 +03:00
|
|
|
|
toHtml =<< liftIO (humanReadableTime editDate)
|
|
|
|
|
emptySpan "1em"
|
|
|
|
|
textButton "accept" $
|
|
|
|
|
JS.acceptEdit (editId, editNode)
|
|
|
|
|
emptySpan "0.5em"
|
|
|
|
|
textButton "try to undo" $
|
|
|
|
|
JS.undoEdit (editId, editNode)
|
|
|
|
|
case mbErr of
|
|
|
|
|
Nothing -> return ()
|
|
|
|
|
Just err -> p_ $ span_ [style_ "background-color:#E57373"] $
|
|
|
|
|
"Can't apply the edit: " >> toHtml err
|
|
|
|
|
renderEdit globalState edit
|
|
|
|
|
|
2016-04-07 22:14:08 +03:00
|
|
|
|
renderEdit :: Monad m => GlobalState -> Edit -> HtmlT m ()
|
|
|
|
|
renderEdit globalState edit = do
|
|
|
|
|
let quote :: Monad m => HtmlT m () -> HtmlT m ()
|
|
|
|
|
quote a = "“" *> a <* "”"
|
|
|
|
|
-- We're searching for everything (items/categories) both in normal lists
|
|
|
|
|
-- and in lists of deleted things. Just in case.
|
|
|
|
|
let allCategories = globalState^.categories ++
|
|
|
|
|
globalState^.categoriesDeleted
|
2016-04-09 00:50:13 +03:00
|
|
|
|
let findCategory catId = fromMaybe err (find (hasUid catId) allCategories)
|
2016-04-07 22:14:08 +03:00
|
|
|
|
where
|
|
|
|
|
err = error ("renderEdit: couldn't find category with uid = " ++
|
|
|
|
|
T.unpack (uidToText catId))
|
|
|
|
|
let findItem itemId = (category, item)
|
|
|
|
|
where
|
|
|
|
|
getItems = view (items <> itemsDeleted)
|
2016-04-09 00:50:13 +03:00
|
|
|
|
ourCategory = any (hasUid itemId) . getItems
|
2016-04-07 22:14:08 +03:00
|
|
|
|
err = error ("renderEdit: couldn't find item with uid = " ++
|
|
|
|
|
T.unpack (uidToText itemId))
|
|
|
|
|
category = fromMaybe err (find ourCategory allCategories)
|
2016-04-09 00:50:13 +03:00
|
|
|
|
item = fromJust (find (hasUid itemId) (getItems category))
|
2016-04-07 22:14:08 +03:00
|
|
|
|
let findTrait itemId traitId = (category, item, trait)
|
|
|
|
|
where
|
|
|
|
|
(category, item) = findItem itemId
|
|
|
|
|
getTraits = view (cons <> consDeleted <> pros <> prosDeleted)
|
|
|
|
|
err = error ("renderEdit: couldn't find trait with uid = " ++
|
|
|
|
|
T.unpack (uidToText traitId))
|
2016-04-09 00:50:13 +03:00
|
|
|
|
trait = fromMaybe err (find (hasUid traitId) (getTraits item))
|
2016-04-07 22:14:08 +03:00
|
|
|
|
|
|
|
|
|
let printCategory catId = do
|
|
|
|
|
let category = findCategory catId
|
2016-07-06 23:50:02 +03:00
|
|
|
|
quote $ a_ [href_ (categoryLink category)] $
|
|
|
|
|
toHtml (category ^. title)
|
2016-04-07 22:14:08 +03:00
|
|
|
|
let printItem itemId = do
|
2016-07-06 23:50:02 +03:00
|
|
|
|
let (category, item) = findItem itemId
|
|
|
|
|
quote $ a_ [href_ (itemLink category item)] $
|
|
|
|
|
toHtml (item ^. name)
|
2016-04-07 22:14:08 +03:00
|
|
|
|
|
|
|
|
|
case edit of
|
|
|
|
|
-- Add
|
|
|
|
|
Edit'AddCategory _catId title' -> p_ $ do
|
|
|
|
|
"added category " >> quote (toHtml title')
|
|
|
|
|
Edit'AddItem catId _itemId name' -> p_ $ do
|
|
|
|
|
"added item " >> quote (toHtml name')
|
|
|
|
|
" to category " >> printCategory catId
|
|
|
|
|
Edit'AddPro itemId _traitId content' -> do
|
|
|
|
|
p_ $ "added pro to item " >> printItem itemId
|
2016-07-24 13:12:17 +03:00
|
|
|
|
blockquote_ $ p_ $ toHtml (toMarkdownInline content')
|
2016-04-07 22:14:08 +03:00
|
|
|
|
Edit'AddCon itemId _traitId content' -> do
|
|
|
|
|
p_ $ "added con to item " >> printItem itemId
|
2016-07-24 13:12:17 +03:00
|
|
|
|
blockquote_ $ p_ $ toHtml (toMarkdownInline content')
|
2016-04-07 22:14:08 +03:00
|
|
|
|
|
|
|
|
|
-- Change category properties
|
|
|
|
|
Edit'SetCategoryTitle _catId oldTitle newTitle -> p_ $ do
|
|
|
|
|
"changed title of category " >> quote (toHtml oldTitle)
|
|
|
|
|
" to " >> quote (toHtml newTitle)
|
2016-05-01 23:17:55 +03:00
|
|
|
|
Edit'SetCategoryGroup catId oldGroup newGroup -> p_ $ do
|
|
|
|
|
"changed group of category " >> printCategory catId
|
|
|
|
|
" from " >> quote (toHtml oldGroup)
|
|
|
|
|
" to " >> quote (toHtml newGroup)
|
2016-05-05 16:50:10 +03:00
|
|
|
|
Edit'SetCategoryStatus catId oldStatus newStatus -> p_ $ do
|
|
|
|
|
"changed status of category " >> printCategory catId
|
|
|
|
|
" from " >> quote (toHtml (show oldStatus))
|
|
|
|
|
" to " >> quote (toHtml (show newStatus))
|
2016-04-07 22:14:08 +03:00
|
|
|
|
Edit'SetCategoryNotes catId oldNotes newNotes -> do
|
2016-11-27 14:38:55 +03:00
|
|
|
|
p_ $ (if T.null oldNotes then "added" else "changed") >>
|
2016-10-20 18:54:20 +03:00
|
|
|
|
" notes of category " >> printCategory catId
|
2016-04-07 22:14:08 +03:00
|
|
|
|
table_ $ tr_ $ do
|
2016-10-17 15:36:17 +03:00
|
|
|
|
unless (T.null oldNotes) $
|
|
|
|
|
td_ $ blockquote_ $ toHtml (toMarkdownBlock oldNotes)
|
2016-07-24 13:12:17 +03:00
|
|
|
|
td_ $ blockquote_ $ toHtml (toMarkdownBlock newNotes)
|
2016-05-22 14:43:46 +03:00
|
|
|
|
Edit'SetCategoryProsConsEnabled catId _oldVal newVal -> do
|
|
|
|
|
if newVal == True
|
|
|
|
|
then p_ $ "enabled pros/cons for category " >> printCategory catId
|
|
|
|
|
else p_ $ "disabled pros/cons for category " >> printCategory catId
|
|
|
|
|
Edit'SetCategoryEcosystemEnabled catId _oldVal newVal -> do
|
|
|
|
|
if newVal == True
|
|
|
|
|
then p_ $ "enabled ecosystem for category " >> printCategory catId
|
|
|
|
|
else p_ $ "disabled ecosystem for category " >> printCategory catId
|
2016-10-17 19:00:15 +03:00
|
|
|
|
Edit'SetCategoryNotesEnabled catId _oldVal newVal -> do
|
|
|
|
|
if newVal == True
|
|
|
|
|
then p_ $ "enabled notes for category " >> printCategory catId
|
|
|
|
|
else p_ $ "disabled notes for category " >> printCategory catId
|
2016-04-07 22:14:08 +03:00
|
|
|
|
|
|
|
|
|
-- Change item properties
|
|
|
|
|
Edit'SetItemName _itemId oldName newName -> p_ $ do
|
|
|
|
|
"changed name of item " >> quote (toHtml oldName)
|
|
|
|
|
" to " >> quote (toHtml newName)
|
|
|
|
|
Edit'SetItemLink itemId oldLink newLink -> p_ $ do
|
|
|
|
|
"changed link of item " >> printItem itemId
|
|
|
|
|
" from " >> code_ (toHtml (show oldLink))
|
|
|
|
|
" to " >> code_ (toHtml (show newLink))
|
|
|
|
|
Edit'SetItemGroup itemId oldGroup newGroup -> p_ $ do
|
|
|
|
|
"changed group of item " >> printItem itemId
|
|
|
|
|
" from " >> code_ (toHtml (show oldGroup))
|
|
|
|
|
" to " >> code_ (toHtml (show newGroup))
|
|
|
|
|
Edit'SetItemKind itemId oldKind newKind -> p_ $ do
|
|
|
|
|
"changed kind of item " >> printItem itemId
|
|
|
|
|
" from " >> code_ (toHtml (show oldKind))
|
|
|
|
|
" to " >> code_ (toHtml (show newKind))
|
|
|
|
|
Edit'SetItemDescription itemId oldDescr newDescr -> do
|
2016-11-27 14:38:55 +03:00
|
|
|
|
p_ $ (if T.null oldDescr then "added" else "changed") >>
|
2016-10-20 18:54:20 +03:00
|
|
|
|
" description of item " >> printItem itemId
|
2016-04-07 22:14:08 +03:00
|
|
|
|
table_ $ tr_ $ do
|
2016-10-17 15:36:17 +03:00
|
|
|
|
unless (T.null oldDescr) $
|
|
|
|
|
td_ $ blockquote_ $ toHtml (toMarkdownBlock oldDescr)
|
2016-07-24 13:12:17 +03:00
|
|
|
|
td_ $ blockquote_ $ toHtml (toMarkdownBlock newDescr)
|
2016-04-07 22:14:08 +03:00
|
|
|
|
Edit'SetItemNotes itemId oldNotes newNotes -> do
|
2016-11-27 14:38:55 +03:00
|
|
|
|
p_ $ (if T.null oldNotes then "added" else "changed") >>
|
2016-10-20 18:54:20 +03:00
|
|
|
|
" notes of item " >> printItem itemId
|
2016-04-07 22:14:08 +03:00
|
|
|
|
table_ $ tr_ $ do
|
2016-10-17 15:36:17 +03:00
|
|
|
|
unless (T.null oldNotes) $
|
|
|
|
|
td_ $ blockquote_ $ toHtml (toMarkdownBlock oldNotes)
|
2016-07-24 13:12:17 +03:00
|
|
|
|
td_ $ blockquote_ $ toHtml (toMarkdownBlock newNotes)
|
2016-04-07 22:14:08 +03:00
|
|
|
|
Edit'SetItemEcosystem itemId oldEcosystem newEcosystem -> do
|
2016-11-27 14:38:55 +03:00
|
|
|
|
p_ $ (if T.null oldEcosystem then "added" else "changed") >>
|
2016-10-20 18:54:20 +03:00
|
|
|
|
" ecosystem of item " >> printItem itemId
|
2016-04-07 22:14:08 +03:00
|
|
|
|
table_ $ tr_ $ do
|
2016-10-17 15:36:17 +03:00
|
|
|
|
unless (T.null oldEcosystem) $
|
|
|
|
|
td_ $ blockquote_ $ toHtml (toMarkdownBlock oldEcosystem)
|
2016-07-24 13:12:17 +03:00
|
|
|
|
td_ $ blockquote_ $ toHtml (toMarkdownBlock newEcosystem)
|
2016-04-07 22:14:08 +03:00
|
|
|
|
|
|
|
|
|
-- Change trait properties
|
|
|
|
|
Edit'SetTraitContent itemId _traitId oldContent newContent -> do
|
2016-11-27 14:38:55 +03:00
|
|
|
|
p_ $ (if T.null oldContent then "added" else "changed") >>
|
2016-10-20 18:54:20 +03:00
|
|
|
|
" trait of item " >> printItem itemId
|
2016-04-07 22:14:08 +03:00
|
|
|
|
table_ $ tr_ $ do
|
2016-10-17 15:36:17 +03:00
|
|
|
|
unless (T.null oldContent) $
|
|
|
|
|
td_ $ blockquote_ $ p_ (toHtml (toMarkdownInline oldContent))
|
2016-07-24 13:12:17 +03:00
|
|
|
|
td_ $ blockquote_ $ p_ (toHtml (toMarkdownInline newContent))
|
2016-04-07 22:14:08 +03:00
|
|
|
|
|
|
|
|
|
-- Delete
|
|
|
|
|
Edit'DeleteCategory catId _pos -> p_ $ do
|
|
|
|
|
"deleted category " >> printCategory catId
|
|
|
|
|
Edit'DeleteItem itemId _pos -> p_ $ do
|
|
|
|
|
let (category, item) = findItem itemId
|
|
|
|
|
"deleted item " >> quote (toHtml (item^.name))
|
|
|
|
|
" from category " >> quote (toHtml (category^.title))
|
|
|
|
|
Edit'DeleteTrait itemId traitId _pos -> do
|
|
|
|
|
let (_, item, trait) = findTrait itemId traitId
|
|
|
|
|
p_ $ "deleted trait from item " >> quote (toHtml (item^.name))
|
2016-04-14 01:56:13 +03:00
|
|
|
|
blockquote_ $ p_ $ toHtml (trait^.content)
|
2016-04-07 22:14:08 +03:00
|
|
|
|
|
|
|
|
|
-- Other
|
|
|
|
|
Edit'MoveItem itemId direction -> p_ $ do
|
|
|
|
|
"moved item " >> printItem itemId
|
|
|
|
|
if direction then " up" else " down"
|
|
|
|
|
Edit'MoveTrait itemId traitId direction -> do
|
|
|
|
|
let (_, item, trait) = findTrait itemId traitId
|
|
|
|
|
p_ $ "moved trait of item " >> quote (toHtml (item^.name)) >>
|
|
|
|
|
if direction then " up" else " down"
|
2016-04-14 01:56:13 +03:00
|
|
|
|
blockquote_ $ p_ $ toHtml (trait^.content)
|
2016-04-07 22:14:08 +03:00
|
|
|
|
|
|
|
|
|
-- TODO: use “data Direction = Up | Down” for directions instead of Bool
|
|
|
|
|
|
2016-11-14 22:10:59 +03:00
|
|
|
|
-- | “Aelve Guide | Haskell”
|
2016-11-27 14:45:38 +03:00
|
|
|
|
haskellHeader :: (MonadReader Config m) => HtmlT m ()
|
2016-11-14 22:10:59 +03:00
|
|
|
|
haskellHeader = do
|
|
|
|
|
h1_ $ mkLink ("Aelve Guide " >> span_ "| Haskell") "/haskell"
|
|
|
|
|
renderSubtitle
|
|
|
|
|
|
2016-11-27 14:45:38 +03:00
|
|
|
|
haskellHeaderMain :: (MonadReader Config m) => HtmlT m ()
|
2016-11-14 22:10:59 +03:00
|
|
|
|
haskellHeaderMain = do
|
|
|
|
|
h1_ $ "Aelve Guide " >> span_ "| Haskell"
|
|
|
|
|
renderSubtitle
|
|
|
|
|
|
2016-03-23 18:28:03 +03:00
|
|
|
|
renderHaskellRoot
|
2016-11-27 14:45:38 +03:00
|
|
|
|
:: (MonadIO m, MonadReader Config m)
|
2016-03-22 01:17:53 +03:00
|
|
|
|
=> GlobalState -> Maybe Text -> HtmlT m ()
|
2016-03-23 18:28:03 +03:00
|
|
|
|
renderHaskellRoot globalState mbSearchQuery =
|
2016-11-14 22:10:59 +03:00
|
|
|
|
wrapPage "Aelve Guide | Haskell" $ do
|
2016-04-20 01:59:29 +03:00
|
|
|
|
onPageLoad $ JS.expandHash ()
|
2016-04-15 23:44:55 +03:00
|
|
|
|
case mbSearchQuery of
|
2016-11-14 22:10:59 +03:00
|
|
|
|
Nothing -> haskellHeaderMain
|
2016-04-15 23:44:55 +03:00
|
|
|
|
-- A search page isn't the main page, so we need a link to the main page
|
2016-11-14 22:10:59 +03:00
|
|
|
|
Just _ -> haskellHeader
|
2016-04-06 01:36:55 +03:00
|
|
|
|
renderNoScriptWarning
|
2016-04-21 17:01:54 +03:00
|
|
|
|
renderSearch mbSearchQuery
|
2016-03-15 15:35:35 +03:00
|
|
|
|
textInput [
|
|
|
|
|
placeholder_ "add a category",
|
2016-08-17 11:18:57 +03:00
|
|
|
|
class_ "add-category",
|
2016-03-15 15:35:35 +03:00
|
|
|
|
autocomplete_ "off",
|
2016-04-21 18:10:58 +03:00
|
|
|
|
onEnter $ JS.addCategoryAndRedirect [inputValue] ]
|
2016-03-15 15:35:35 +03:00
|
|
|
|
case mbSearchQuery of
|
|
|
|
|
Nothing -> renderCategoryList (globalState^.categories)
|
|
|
|
|
Just query' -> do
|
|
|
|
|
let queryWords = T.words query'
|
|
|
|
|
let rank :: Category -> Int
|
|
|
|
|
rank cat = sum [
|
|
|
|
|
length (queryWords `intersect` (cat^..items.each.name)),
|
|
|
|
|
length (queryWords `intersect` T.words (cat^.title)) ]
|
|
|
|
|
let rankedCategories
|
|
|
|
|
| null queryWords = globalState^.categories
|
|
|
|
|
| otherwise = filter ((/= 0) . rank) .
|
|
|
|
|
reverse . sortOn rank
|
|
|
|
|
$ globalState^.categories
|
2016-05-01 23:17:55 +03:00
|
|
|
|
renderSearchResults rankedCategories
|
2016-03-15 15:35:35 +03:00
|
|
|
|
-- TODO: maybe add a button like “give me random category that is
|
|
|
|
|
-- unfinished”
|
|
|
|
|
|
2016-03-23 18:28:03 +03:00
|
|
|
|
renderCategoryPage
|
2016-11-27 14:45:38 +03:00
|
|
|
|
:: (MonadIO m, MonadReader Config m)
|
2016-04-21 16:47:14 +03:00
|
|
|
|
=> Category -> HtmlT m ()
|
2016-05-01 16:28:10 +03:00
|
|
|
|
renderCategoryPage category = do
|
2016-05-10 03:45:20 +03:00
|
|
|
|
wrapPage (category^.title <> " – Haskell – Aelve Guide") $ do
|
2016-04-20 01:59:29 +03:00
|
|
|
|
onPageLoad $ JS.expandHash ()
|
2016-11-14 22:10:59 +03:00
|
|
|
|
haskellHeader
|
2016-04-06 01:36:55 +03:00
|
|
|
|
renderNoScriptWarning
|
2016-04-21 17:01:54 +03:00
|
|
|
|
renderSearch Nothing
|
2016-03-23 18:28:03 +03:00
|
|
|
|
renderCategory category
|
|
|
|
|
|
2016-07-25 19:47:49 +03:00
|
|
|
|
renderNoScriptWarning :: Monad m => HtmlT m ()
|
2016-04-06 01:36:55 +03:00
|
|
|
|
renderNoScriptWarning =
|
|
|
|
|
noscript_ $ div_ [id_ "noscript-message"] $
|
2016-07-24 13:12:17 +03:00
|
|
|
|
toHtml $ toMarkdownBlock [text|
|
2016-04-06 01:36:55 +03:00
|
|
|
|
You have Javascript disabled! This site works fine without
|
|
|
|
|
Javascript, but since all editing needs Javascript to work,
|
|
|
|
|
you won't be able to edit anything.
|
|
|
|
|
|]
|
|
|
|
|
|
2016-04-21 16:47:14 +03:00
|
|
|
|
renderDonate
|
2016-07-25 19:47:49 +03:00
|
|
|
|
:: (MonadIO m, MonadReader Config m) => HtmlT m ()
|
2016-03-23 18:28:03 +03:00
|
|
|
|
renderDonate = wrapPage "Donate to Artyom" $ do
|
|
|
|
|
toHtmlRaw =<< liftIO (readFile "static/donate.html")
|
2016-03-15 15:35:35 +03:00
|
|
|
|
|
2016-05-05 23:11:08 +03:00
|
|
|
|
renderStaticMd
|
2016-07-25 19:47:49 +03:00
|
|
|
|
:: (MonadIO m, MonadReader Config m)
|
2016-05-05 23:11:08 +03:00
|
|
|
|
=> Text -> String -> HtmlT m ()
|
|
|
|
|
renderStaticMd t fn = wrapPage t $
|
2016-07-24 13:12:17 +03:00
|
|
|
|
toHtml . toMarkdownBlock =<< liftIO (T.readFile ("static/" ++ fn))
|
2016-05-02 21:27:49 +03:00
|
|
|
|
|
2016-03-19 02:40:00 +03:00
|
|
|
|
-- Include all the necessary things
|
2016-03-22 01:17:53 +03:00
|
|
|
|
wrapPage
|
2016-07-25 19:47:49 +03:00
|
|
|
|
:: (MonadIO m, MonadReader Config m)
|
2016-03-22 01:17:53 +03:00
|
|
|
|
=> Text -- ^ Page title
|
|
|
|
|
-> HtmlT m ()
|
|
|
|
|
-> HtmlT m ()
|
2016-03-19 02:40:00 +03:00
|
|
|
|
wrapPage pageTitle page = doctypehtml_ $ do
|
|
|
|
|
head_ $ do
|
|
|
|
|
title_ (toHtml pageTitle)
|
2016-03-19 03:55:31 +03:00
|
|
|
|
meta_ [name_ "viewport",
|
|
|
|
|
content_ "width=device-width, initial-scale=1.0, user-scalable=yes"]
|
2016-05-11 01:53:38 +03:00
|
|
|
|
link_ [rel_ "icon", href_ "/favicon.ico"]
|
2016-08-17 11:18:57 +03:00
|
|
|
|
googleToken <- _googleToken <$> lift ask
|
|
|
|
|
unless (T.null googleToken) $
|
|
|
|
|
meta_ [name_ "google-site-verification", content_ googleToken]
|
2016-03-23 12:22:14 +03:00
|
|
|
|
-- Report all Javascript errors with alerts
|
|
|
|
|
script_ [text|
|
|
|
|
|
window.onerror = function (msg, url, lineNo, columnNo, error) {
|
|
|
|
|
alert("Error in "+url+" at "+lineNo+":"+columnNo+": "+msg+
|
|
|
|
|
"\n\n"+
|
|
|
|
|
"========== Please report it! =========="+
|
|
|
|
|
"\n\n"+
|
|
|
|
|
"https://github.com/aelve/guide/issues");
|
|
|
|
|
return false; };
|
|
|
|
|
|]
|
2016-05-27 17:19:29 +03:00
|
|
|
|
includeJS "/jquery.js"
|
2016-06-19 00:52:19 +03:00
|
|
|
|
-- for modal dialogs
|
|
|
|
|
includeJS "/magnific-popup.js"
|
|
|
|
|
includeCSS "/magnific-popup.css"
|
2016-03-19 02:40:00 +03:00
|
|
|
|
-- See Note [autosize]
|
2016-05-27 17:19:29 +03:00
|
|
|
|
includeJS "/autosize.js"
|
2016-03-19 02:40:00 +03:00
|
|
|
|
onPageLoad (JS "autosize($('textarea'));")
|
2016-04-09 03:36:38 +03:00
|
|
|
|
-- The order is important – markup.css overrides some rules from
|
|
|
|
|
-- highlight.css (e.g. div.sourceCode), css.css overrides the rule for
|
|
|
|
|
-- a.anchor from markup.css.
|
|
|
|
|
--
|
|
|
|
|
-- TODO: maybe use !important or something instead?
|
2016-03-19 02:40:00 +03:00
|
|
|
|
includeCSS "/highlight.css"
|
2016-04-09 03:36:38 +03:00
|
|
|
|
includeCSS "/markup.css"
|
2016-03-19 02:40:00 +03:00
|
|
|
|
includeCSS "/css.css"
|
2016-04-16 23:06:59 +03:00
|
|
|
|
includeCSS "/loader.css"
|
2016-03-19 02:40:00 +03:00
|
|
|
|
-- Include definitions of all Javascript functions that we have defined
|
|
|
|
|
-- in this file. (This isn't an actual file, so don't look for it in the
|
|
|
|
|
-- static folder – it's generated and served in 'otherMethods'.)
|
|
|
|
|
includeJS "/js.js"
|
2016-03-27 02:34:07 +03:00
|
|
|
|
-- CSS that makes 'shown' and 'noScriptShown' work;
|
|
|
|
|
-- see Note [show-hide]
|
2016-03-19 02:40:00 +03:00
|
|
|
|
noscript_ $ style_ [text|
|
|
|
|
|
.section:not(.noscript-shown) {display:none;}
|
|
|
|
|
|]
|
|
|
|
|
script_ [text|
|
|
|
|
|
var sheet = document.createElement('style');
|
|
|
|
|
sheet.innerHTML = '.section:not(.shown) {display:none;}';
|
|
|
|
|
// “head” instead of “body” because body isn't loaded yet
|
|
|
|
|
document.head.appendChild(sheet);
|
|
|
|
|
|]
|
|
|
|
|
|
|
|
|
|
body_ $ do
|
2016-04-16 23:06:59 +03:00
|
|
|
|
script_ $ fromJS $ JS.createAjaxIndicator ()
|
2016-03-23 18:28:03 +03:00
|
|
|
|
div_ [id_ "main"] $
|
|
|
|
|
page
|
2016-03-19 02:40:00 +03:00
|
|
|
|
div_ [id_ "footer"] $ do
|
2016-05-03 03:27:30 +03:00
|
|
|
|
mapM_ (div_ [class_ "footer-item"]) $
|
|
|
|
|
[ do "made by "
|
|
|
|
|
mkLink "Artyom" "https://artyom.me"
|
|
|
|
|
, do mkLink "source" "https://github.com/aelve/guide"
|
|
|
|
|
"/"
|
|
|
|
|
mkLink "issue tracker" "https://github.com/aelve/guide/issues"
|
|
|
|
|
, mkLink "rules" "/unwritten-rules"
|
2016-09-06 19:09:52 +03:00
|
|
|
|
, mkLink "donate" "/donate"
|
2016-05-03 03:27:30 +03:00
|
|
|
|
, do "licensed under "
|
2016-05-05 23:11:08 +03:00
|
|
|
|
mkLink "CC+ BY-SA 4.0" "/license"
|
2016-05-03 03:27:30 +03:00
|
|
|
|
]
|
2016-03-19 02:40:00 +03:00
|
|
|
|
|
2016-11-27 14:45:38 +03:00
|
|
|
|
renderSearch :: (MonadIO m) => Maybe Text -> HtmlT m ()
|
2016-08-17 11:18:57 +03:00
|
|
|
|
renderSearch mbSearchQuery =
|
|
|
|
|
mustache "search" $ A.object [
|
|
|
|
|
"query" A..= mbSearchQuery ]
|
2016-04-21 17:01:54 +03:00
|
|
|
|
|
2016-05-01 16:28:10 +03:00
|
|
|
|
-- If the presentation of the category list ever changes (e.g. to include
|
|
|
|
|
-- lists of items in categories, or their counts, or something), you might
|
|
|
|
|
-- have to start invalidating 'CacheCategoryList' in more things in
|
|
|
|
|
-- 'Cache.invalidateCache'.
|
2016-07-25 19:47:49 +03:00
|
|
|
|
renderCategoryList :: MonadIO m => [Category] -> HtmlT m ()
|
2016-11-14 22:10:59 +03:00
|
|
|
|
renderCategoryList allCats = cached CacheCategoryList $ do
|
2016-05-01 23:17:55 +03:00
|
|
|
|
div_ [id_ "categories"] $
|
2016-11-14 22:10:59 +03:00
|
|
|
|
for_ (groupWith (view group_) allCats) $ \catsInGroup ->
|
2016-05-01 23:17:55 +03:00
|
|
|
|
div_ [class_ "category-group"] $ do
|
2016-11-14 22:10:59 +03:00
|
|
|
|
-- Grandcategory name
|
|
|
|
|
h2_ $ toHtml (catsInGroup^?!_head.group_)
|
|
|
|
|
-- Finished categories
|
|
|
|
|
do let cats = filter ((== CategoryFinished) . view status) catsInGroup
|
|
|
|
|
unless (null cats) $
|
|
|
|
|
div_ [class_ "categories-finished"] $ do
|
|
|
|
|
mapM_ mkCategoryLink cats
|
|
|
|
|
-- In-progress categories, separated with commas
|
|
|
|
|
do let cats = filter ((== CategoryWIP) . view status) catsInGroup
|
|
|
|
|
unless (null cats) $
|
|
|
|
|
div_ [class_ "categories-wip"] $ do
|
|
|
|
|
h3_ "In progress"
|
|
|
|
|
p_ $ sequence_ $ intersperse ", " $
|
|
|
|
|
map mkCategoryLink cats
|
|
|
|
|
-- Stub categories, separated with commas
|
|
|
|
|
do let cats = filter ((== CategoryStub) . view status) catsInGroup
|
|
|
|
|
unless (null cats) $
|
|
|
|
|
div_ [class_ "categories-stub"] $ do
|
|
|
|
|
h3_ "To be written"
|
|
|
|
|
p_ $ sequence_ $ intersperse ", " $
|
|
|
|
|
map mkCategoryLink cats
|
|
|
|
|
where
|
|
|
|
|
-- TODO: this link shouldn't be absolute [absolute-links]
|
|
|
|
|
mkCategoryLink :: Category -> HtmlT IO ()
|
|
|
|
|
mkCategoryLink category =
|
|
|
|
|
a_ [class_ "category-link", href_ (categoryLink category)] $
|
|
|
|
|
toHtml (category^.title)
|
2016-05-01 23:17:55 +03:00
|
|
|
|
|
|
|
|
|
renderSearchResults :: Monad m => [Category] -> HtmlT m ()
|
|
|
|
|
renderSearchResults cats = do
|
2016-11-14 22:10:59 +03:00
|
|
|
|
div_ [id_ "categories-search-results"] $
|
2016-04-21 18:10:58 +03:00
|
|
|
|
for_ cats $ \category -> do
|
2016-11-14 22:10:59 +03:00
|
|
|
|
a_ [class_ "category-link", href_ (categoryLink category)] $
|
2016-04-21 18:10:58 +03:00
|
|
|
|
toHtml (category^.title)
|
2016-03-15 15:35:35 +03:00
|
|
|
|
|
2016-05-05 16:50:10 +03:00
|
|
|
|
renderCategoryInfo :: MonadIO m => Category -> HtmlT m ()
|
|
|
|
|
renderCategoryInfo category = cached (CacheCategoryInfo (category^.uid)) $ do
|
|
|
|
|
let thisId = "category-info-" <> uidToText (category^.uid)
|
2016-03-15 15:35:35 +03:00
|
|
|
|
this = JS.selectId thisId
|
2016-05-05 16:50:10 +03:00
|
|
|
|
div_ [id_ thisId, class_ "category-info"] $ do
|
|
|
|
|
|
|
|
|
|
section "normal" [shown, noScriptShown] $ h2_ $ do
|
|
|
|
|
-- TODO: this link shouldn't be absolute [absolute-links]
|
|
|
|
|
span_ [class_ "controls"] $
|
2016-09-09 20:06:17 +03:00
|
|
|
|
a_ [class_ "category-feed",
|
|
|
|
|
href_ ("/haskell/feed/category/" <> uidToText (category^.uid))] $
|
2016-05-05 16:50:10 +03:00
|
|
|
|
img_ [src_ "/rss-alt.svg",
|
|
|
|
|
alt_ "category feed", title_ "category feed"]
|
2016-08-22 17:10:29 +03:00
|
|
|
|
a_ [href_ (categoryLink category), class_ "category-title"] $
|
2016-03-19 02:40:00 +03:00
|
|
|
|
toHtml (category^.title)
|
2016-03-15 15:35:35 +03:00
|
|
|
|
emptySpan "1em"
|
2016-05-01 23:17:55 +03:00
|
|
|
|
span_ [class_ "group"] $
|
|
|
|
|
toHtml (category^.group_)
|
|
|
|
|
emptySpan "1em"
|
2016-03-15 15:35:35 +03:00
|
|
|
|
textButton "edit" $
|
|
|
|
|
JS.switchSection (this, "editing" :: Text)
|
2016-04-07 15:54:11 +03:00
|
|
|
|
emptySpan "1em"
|
|
|
|
|
textButton "delete" $
|
2016-04-22 01:26:45 +03:00
|
|
|
|
JS.deleteCategoryAndRedirect [category^.uid]
|
2016-03-15 15:35:35 +03:00
|
|
|
|
|
2016-05-05 16:50:10 +03:00
|
|
|
|
section "editing" [] $ do
|
|
|
|
|
let formSubmitHandler formNode =
|
|
|
|
|
JS.submitCategoryInfo (this, category^.uid, formNode)
|
|
|
|
|
form_ [onFormSubmit formSubmitHandler] $ do
|
|
|
|
|
-- All inputs have "autocomplete = off" thanks to
|
|
|
|
|
-- <http://stackoverflow.com/q/8311455>
|
|
|
|
|
label_ $ do
|
|
|
|
|
"Title" >> br_ []
|
|
|
|
|
input_ [type_ "text", name_ "title",
|
|
|
|
|
autocomplete_ "off",
|
|
|
|
|
value_ (category^.title)]
|
|
|
|
|
br_ []
|
|
|
|
|
label_ $ do
|
|
|
|
|
"Group" >> br_ []
|
|
|
|
|
input_ [type_ "text", name_ "group",
|
|
|
|
|
autocomplete_ "off",
|
|
|
|
|
value_ (category^.group_)]
|
|
|
|
|
br_ []
|
|
|
|
|
label_ $ do
|
|
|
|
|
"Status" >> br_ []
|
2016-05-22 14:43:46 +03:00
|
|
|
|
select_ [name_ "status", autocomplete_ "off"] $ do
|
2016-05-05 16:50:10 +03:00
|
|
|
|
option_ [value_ "finished"] "Complete"
|
|
|
|
|
& selectedIf (category^.status == CategoryFinished)
|
|
|
|
|
option_ [value_ "wip"] "Work in progress"
|
|
|
|
|
& selectedIf (category^.status == CategoryWIP)
|
|
|
|
|
option_ [value_ "stub"] "Stub"
|
|
|
|
|
& selectedIf (category^.status == CategoryStub)
|
|
|
|
|
br_ []
|
2016-05-22 14:43:46 +03:00
|
|
|
|
label_ $ do
|
|
|
|
|
input_ [type_ "checkbox", name_ "pros-cons-enabled",
|
|
|
|
|
autocomplete_ "off"]
|
|
|
|
|
& checkedIf (category^.prosConsEnabled)
|
|
|
|
|
"Pros/cons enabled"
|
|
|
|
|
br_ []
|
|
|
|
|
label_ $ do
|
|
|
|
|
input_ [type_ "checkbox", name_ "ecosystem-enabled",
|
|
|
|
|
autocomplete_ "off"]
|
|
|
|
|
& checkedIf (category^.ecosystemEnabled)
|
|
|
|
|
"“Ecosystem” field enabled"
|
|
|
|
|
br_ []
|
2016-10-17 19:00:15 +03:00
|
|
|
|
label_ $ do
|
|
|
|
|
input_ [type_ "checkbox", name_ "notes-enabled",
|
|
|
|
|
autocomplete_ "off"]
|
|
|
|
|
& checkedIf (category^.notesEnabled)
|
|
|
|
|
"“Notes” field enabled"
|
|
|
|
|
br_ []
|
2016-08-29 23:38:17 +03:00
|
|
|
|
input_ [type_ "submit", value_ "Save", class_ "save"]
|
|
|
|
|
button "Cancel" [class_ "cancel"] $
|
2016-05-05 16:50:10 +03:00
|
|
|
|
JS.switchSection (this, "normal" :: Text)
|
2016-03-15 15:35:35 +03:00
|
|
|
|
|
2016-07-25 19:47:49 +03:00
|
|
|
|
renderCategoryNotes :: MonadIO m => Category -> HtmlT m ()
|
2016-05-01 16:28:10 +03:00
|
|
|
|
renderCategoryNotes category = cached (CacheCategoryNotes (category^.uid)) $ do
|
2016-03-15 15:35:35 +03:00
|
|
|
|
let thisId = "category-notes-" <> uidToText (category^.uid)
|
|
|
|
|
this = JS.selectId thisId
|
2016-04-23 19:30:43 +03:00
|
|
|
|
div_ [id_ thisId, class_ "category-notes"] $ do
|
2016-03-15 15:35:35 +03:00
|
|
|
|
|
|
|
|
|
section "normal" [shown, noScriptShown] $ do
|
2016-04-21 19:28:35 +03:00
|
|
|
|
div_ [class_ "notes-like"] $ do
|
2016-04-22 01:06:02 +03:00
|
|
|
|
if markdownNull (category^.notes)
|
2016-04-21 19:28:35 +03:00
|
|
|
|
then p_ "write something here!"
|
|
|
|
|
else toHtml (category^.notes)
|
2016-03-15 15:35:35 +03:00
|
|
|
|
textButton "edit description" $
|
2016-07-27 15:33:53 +03:00
|
|
|
|
JS.switchSection (this, "editing" :: Text) <>
|
|
|
|
|
JS.focusOn [(this `JS.selectSection` "editing")
|
|
|
|
|
`JS.selectChildren`
|
|
|
|
|
JS.selectClass "editor"]
|
2016-03-15 15:35:35 +03:00
|
|
|
|
|
2016-04-15 16:15:02 +03:00
|
|
|
|
section "editing" [] $ do
|
2016-04-22 01:06:02 +03:00
|
|
|
|
contents <- if markdownNull (category^.notes)
|
2016-07-24 13:12:17 +03:00
|
|
|
|
then liftIO $ toMarkdownBlock <$>
|
2016-04-15 16:15:02 +03:00
|
|
|
|
T.readFile "static/category-notes-template.md"
|
|
|
|
|
else return (category^.notes)
|
2016-03-15 15:35:35 +03:00
|
|
|
|
markdownEditor
|
2016-07-27 15:33:53 +03:00
|
|
|
|
[rows_ "10", class_ " editor "]
|
2016-04-15 16:15:02 +03:00
|
|
|
|
contents
|
2016-06-20 14:59:48 +03:00
|
|
|
|
(\val -> JS.submitCategoryNotes
|
|
|
|
|
(this, category^.uid, category^.notes.mdText, val))
|
2016-03-15 15:35:35 +03:00
|
|
|
|
(JS.switchSection (this, "normal" :: Text))
|
2016-07-21 22:15:15 +03:00
|
|
|
|
"or press Ctrl+Enter to save"
|
2016-03-15 15:35:35 +03:00
|
|
|
|
|
2016-07-25 19:47:49 +03:00
|
|
|
|
renderCategory :: MonadIO m => Category -> HtmlT m ()
|
2016-05-01 16:28:10 +03:00
|
|
|
|
renderCategory category = cached (CacheCategory (category^.uid)) $ do
|
2016-04-07 15:54:11 +03:00
|
|
|
|
div_ [class_ "category", id_ (categoryNodeId category)] $ do
|
2016-05-05 16:50:10 +03:00
|
|
|
|
renderCategoryInfo category
|
2016-03-15 15:35:35 +03:00
|
|
|
|
renderCategoryNotes category
|
|
|
|
|
itemsNode <- div_ [class_ "items"] $ do
|
|
|
|
|
mapM_ (renderItem category) (category^.items)
|
|
|
|
|
thisNode
|
|
|
|
|
textInput [
|
2016-08-29 23:38:17 +03:00
|
|
|
|
class_ " add-item ",
|
2016-03-15 15:35:35 +03:00
|
|
|
|
placeholder_ "add an item",
|
|
|
|
|
autocomplete_ "off",
|
|
|
|
|
onEnter $ JS.addItem (itemsNode, category^.uid, inputValue) <>
|
|
|
|
|
clearInput ]
|
|
|
|
|
|
|
|
|
|
getItemHue :: Category -> Item -> Hue
|
|
|
|
|
getItemHue category item = case item^.group_ of
|
|
|
|
|
Nothing -> NoHue
|
|
|
|
|
Just s -> M.findWithDefault NoHue s (category^.groups)
|
|
|
|
|
|
2016-05-22 14:43:46 +03:00
|
|
|
|
{- Note [enabled sections]
|
|
|
|
|
~~~~~~~~~~~~~~~~~~~~~~~~~~
|
|
|
|
|
|
2016-10-20 18:54:20 +03:00
|
|
|
|
Categories have flags that enable/disable showing some sections of the items
|
|
|
|
|
(currently pros/cons, ecosystem and notes); this is done because for some
|
|
|
|
|
items (like books, or people) “ecosystem” might not make any sense, and
|
|
|
|
|
pros/cons don't make sense for categories that contain diverse items.
|
|
|
|
|
|
|
|
|
|
When we change those flags (by editing category info), we want to update the
|
|
|
|
|
way items are shown (without reloading the page). So, if the “show ecosystem”
|
|
|
|
|
flag has been set and we unset it, we want to hide the ecosystem section in
|
|
|
|
|
all items belonging to the category. This happens in 'JS.submitCategoryInfo'.
|
|
|
|
|
|
|
|
|
|
If the category has showing pros/cons (or ecosystem, or both) disabled, we
|
|
|
|
|
have to render traits and ecosystem as hidden (we can't just not render them
|
|
|
|
|
at all, because then we wouldn't be able to un-hide them). How could we do
|
|
|
|
|
it? If we do it in 'renderItemTraits' or 'renderItemEcosystem', this would
|
|
|
|
|
mean that cached versions of traits/ecosystem/notes would have to be
|
|
|
|
|
rerendered whenever prosConsEnabled/ecosystemEnabled is changed. So, instead
|
|
|
|
|
we do a somewhat inelegant thing: we wrap traits/ecosystem/notes into yet
|
|
|
|
|
another <div>, and set “display:none” on it. 'JS.submitCategoryInfo' operates
|
|
|
|
|
on those <div>s.
|
2016-05-22 14:43:46 +03:00
|
|
|
|
-}
|
|
|
|
|
|
2016-03-15 15:35:35 +03:00
|
|
|
|
-- TODO: perhaps use jQuery Touch Punch or something to allow dragging items
|
|
|
|
|
-- instead of using arrows? Touch Punch works on mobile, too
|
2016-07-25 19:47:49 +03:00
|
|
|
|
renderItem :: MonadIO m => Category -> Item -> HtmlT m ()
|
2016-05-01 16:28:10 +03:00
|
|
|
|
renderItem category item = cached (CacheItem (item^.uid)) $ do
|
2016-03-20 13:30:10 +03:00
|
|
|
|
-- The id is used for links in feeds, and for anchor links
|
2016-04-07 15:54:11 +03:00
|
|
|
|
div_ [id_ (itemNodeId item), class_ "item"] $ do
|
2016-03-17 03:35:56 +03:00
|
|
|
|
renderItemInfo category item
|
|
|
|
|
let bg = hueToLightColor $ getItemHue category item
|
|
|
|
|
div_ [class_ "item-body", style_ ("background-color:" <> bg)] $ do
|
2016-05-22 14:43:46 +03:00
|
|
|
|
-- See Note [enabled sections]
|
2016-03-17 03:35:56 +03:00
|
|
|
|
renderItemDescription item
|
2016-05-22 14:43:46 +03:00
|
|
|
|
hiddenIf (not (category^.prosConsEnabled)) $
|
|
|
|
|
div_ [class_ "pros-cons-wrapper"] $
|
|
|
|
|
renderItemTraits item
|
|
|
|
|
hiddenIf (not (category^.ecosystemEnabled)) $
|
|
|
|
|
div_ [class_ "ecosystem-wrapper"] $
|
|
|
|
|
renderItemEcosystem item
|
2016-10-17 19:00:15 +03:00
|
|
|
|
hiddenIf (not (category^.notesEnabled)) $
|
|
|
|
|
div_ [class_ "notes-wrapper"] $
|
|
|
|
|
renderItemNotes category item
|
2016-03-15 15:35:35 +03:00
|
|
|
|
|
|
|
|
|
-- TODO: warn when a library isn't on Hackage but is supposed to be
|
2016-03-17 03:35:56 +03:00
|
|
|
|
|
2016-11-27 14:45:38 +03:00
|
|
|
|
renderItemTitle :: (MonadIO m) => Item -> HtmlT m ()
|
2016-08-17 11:18:57 +03:00
|
|
|
|
renderItemTitle item =
|
|
|
|
|
mustache "item-title" $ A.object [
|
|
|
|
|
"item" A..= item ]
|
2016-03-19 21:36:21 +03:00
|
|
|
|
|
2016-03-15 15:35:35 +03:00
|
|
|
|
-- TODO: give a link to oldest available docs when the new docs aren't there
|
2016-11-27 14:45:38 +03:00
|
|
|
|
renderItemInfo :: (MonadIO m) => Category -> Item -> HtmlT m ()
|
2016-05-01 16:28:10 +03:00
|
|
|
|
renderItemInfo cat item = cached (CacheItemInfo (item^.uid)) $ do
|
2016-08-17 11:18:57 +03:00
|
|
|
|
let itemkindname :: Text
|
|
|
|
|
itemkindname = case item^.kind of
|
|
|
|
|
Library{} -> "library"
|
|
|
|
|
Tool{} -> "tool"
|
|
|
|
|
Other{} -> "other"
|
|
|
|
|
mustache "item-info" $ A.object [
|
|
|
|
|
"category" A..= cat,
|
|
|
|
|
"item" A..= item,
|
|
|
|
|
"link_to_item" A..= itemLink cat item,
|
|
|
|
|
"possible_kinds" A..= do
|
|
|
|
|
kindname <- ["library", "tool", "other"]
|
|
|
|
|
return $ A.object [
|
|
|
|
|
"name" A..= kindname,
|
|
|
|
|
"caption" A..= over _head toUpper kindname,
|
|
|
|
|
"selected" A..= (itemkindname == kindname) ],
|
2016-09-03 21:49:55 +03:00
|
|
|
|
"category_groups" A..= do
|
|
|
|
|
gr <- M.keys (cat^.groups)
|
|
|
|
|
return $ A.object [
|
|
|
|
|
"name" A..= gr,
|
|
|
|
|
"selected" A..= (Just gr == item^.group_) ],
|
2016-08-17 11:18:57 +03:00
|
|
|
|
"item_no_group" A..= isNothing (item^.group_),
|
|
|
|
|
"item_color" A..= A.object [
|
|
|
|
|
"dark" A..= hueToDarkColor (getItemHue cat item),
|
|
|
|
|
"light" A..= hueToLightColor (getItemHue cat item) ] ]
|
2016-03-15 15:35:35 +03:00
|
|
|
|
|
2016-07-25 19:47:49 +03:00
|
|
|
|
renderItemDescription :: MonadIO m => Item -> HtmlT m ()
|
2016-08-19 04:07:45 +03:00
|
|
|
|
renderItemDescription item = cached (CacheItemDescription (item^.uid)) $
|
|
|
|
|
mustache "item-description" $ A.object [
|
|
|
|
|
"item" A..= item ]
|
2016-03-15 15:35:35 +03:00
|
|
|
|
|
2016-07-25 19:47:49 +03:00
|
|
|
|
renderItemEcosystem :: MonadIO m => Item -> HtmlT m ()
|
2016-05-01 16:28:10 +03:00
|
|
|
|
renderItemEcosystem item = cached (CacheItemEcosystem (item^.uid)) $ do
|
2016-03-17 02:52:40 +03:00
|
|
|
|
let thisId = "item-ecosystem-" <> uidToText (item^.uid)
|
|
|
|
|
this = JS.selectId thisId
|
2016-03-17 03:35:56 +03:00
|
|
|
|
div_ [id_ thisId, class_ "item-ecosystem"] $ do
|
2016-03-17 02:52:40 +03:00
|
|
|
|
|
|
|
|
|
section "normal" [shown, noScriptShown] $ do
|
2016-04-22 16:22:46 +03:00
|
|
|
|
strong_ "Ecosystem"
|
|
|
|
|
emptySpan "0.5em"
|
|
|
|
|
imgButton "edit ecosystem" "/pencil.svg"
|
2016-09-17 01:07:07 +03:00
|
|
|
|
[style_ "width:12px;opacity:0.5", class_ " edit-item-ecosystem "] $
|
2016-07-27 15:33:53 +03:00
|
|
|
|
JS.switchSection (this, "editing" :: Text) <>
|
|
|
|
|
JS.focusOn [(this `JS.selectSection` "editing")
|
|
|
|
|
`JS.selectChildren`
|
|
|
|
|
JS.selectClass "editor"]
|
2016-09-17 01:07:07 +03:00
|
|
|
|
div_ [class_ "notes-like"] $ do
|
|
|
|
|
unless (markdownNull (item^.ecosystem)) $
|
|
|
|
|
toHtml (item^.ecosystem)
|
2016-03-17 02:52:40 +03:00
|
|
|
|
|
2016-04-22 16:22:46 +03:00
|
|
|
|
section "editing" [] $ do
|
|
|
|
|
strong_ "Ecosystem"
|
|
|
|
|
emptySpan "0.5em"
|
2016-05-13 01:56:17 +03:00
|
|
|
|
imgButton "quit editing ecosystem" "/pencil.svg"
|
2016-09-17 01:07:07 +03:00
|
|
|
|
[style_ "width:12px;opacity:0.5", class_ " edit-item-ecosystem "] $
|
2016-04-22 16:22:46 +03:00
|
|
|
|
JS.switchSection (this, "normal" :: Text)
|
2016-03-17 15:29:45 +03:00
|
|
|
|
markdownEditor
|
2016-07-27 15:33:53 +03:00
|
|
|
|
[rows_ "3", class_ " editor "]
|
2016-03-17 02:52:40 +03:00
|
|
|
|
(item^.ecosystem)
|
2016-06-20 13:13:09 +03:00
|
|
|
|
(\val -> JS.submitItemEcosystem
|
|
|
|
|
(this, item^.uid, item^.ecosystem.mdText, val))
|
2016-03-17 15:29:45 +03:00
|
|
|
|
(JS.switchSection (this, "normal" :: Text))
|
2016-07-21 22:15:15 +03:00
|
|
|
|
"or press Ctrl+Enter to save"
|
2016-03-17 02:52:40 +03:00
|
|
|
|
|
2016-07-25 19:47:49 +03:00
|
|
|
|
renderItemTraits :: MonadIO m => Item -> HtmlT m ()
|
2016-05-01 16:28:10 +03:00
|
|
|
|
renderItemTraits item = cached (CacheItemTraits (item^.uid)) $ do
|
2016-03-17 03:35:56 +03:00
|
|
|
|
div_ [class_ "item-traits"] $ do
|
2016-03-15 15:35:35 +03:00
|
|
|
|
div_ [class_ "traits-groups-container"] $ do
|
|
|
|
|
div_ [class_ "traits-group"] $ do
|
2016-03-17 03:02:51 +03:00
|
|
|
|
strong_ "Pros"
|
2016-05-13 01:56:17 +03:00
|
|
|
|
this <- thisNode
|
|
|
|
|
emptySpan "0.5em"
|
|
|
|
|
sectionSpan "normal" [shown, noScriptShown] $ do
|
|
|
|
|
imgButton "edit pros" "/pencil.svg"
|
|
|
|
|
[style_ "width:12px;opacity:0.5"] $
|
|
|
|
|
JS.switchSectionsEverywhere (this, "editable" :: Text)
|
|
|
|
|
sectionSpan "editable" [] $ do
|
|
|
|
|
imgButton "quit editing pros" "/pencil.svg"
|
|
|
|
|
[style_ "width:12px;opacity:0.5"] $
|
|
|
|
|
JS.switchSectionsEverywhere (this, "normal" :: Text)
|
2016-03-16 15:46:29 +03:00
|
|
|
|
-- We can't use 'thisNode' inside <ul> because it creates a <span>
|
|
|
|
|
-- and only <li> elements can be children of <ul>
|
2016-03-19 00:05:01 +03:00
|
|
|
|
listUid <- randomLongUid
|
2016-03-16 15:46:29 +03:00
|
|
|
|
ul_ [uid_ listUid] $
|
2016-03-15 15:35:35 +03:00
|
|
|
|
mapM_ (renderTrait (item^.uid)) (item^.pros)
|
2016-05-13 01:56:17 +03:00
|
|
|
|
section "editable" [] $ do
|
2016-03-15 15:35:35 +03:00
|
|
|
|
smallMarkdownEditor
|
|
|
|
|
[rows_ "3", placeholder_ "add pro"]
|
2016-07-24 13:12:17 +03:00
|
|
|
|
(toMarkdownInline "")
|
2016-03-16 15:46:29 +03:00
|
|
|
|
(\val -> JS.addPro (JS.selectUid listUid, item^.uid, val) <>
|
2016-03-15 15:35:35 +03:00
|
|
|
|
JS.assign val ("" :: Text))
|
|
|
|
|
Nothing
|
2016-07-21 22:24:06 +03:00
|
|
|
|
"press Ctrl+Enter or Enter to add"
|
2016-05-13 01:56:17 +03:00
|
|
|
|
textButton "edit off" $
|
|
|
|
|
JS.switchSectionsEverywhere(this, "normal" :: Text)
|
|
|
|
|
|
2016-03-15 15:35:35 +03:00
|
|
|
|
div_ [class_ "traits-group"] $ do
|
2016-03-17 03:02:51 +03:00
|
|
|
|
strong_ "Cons"
|
2016-05-13 01:56:17 +03:00
|
|
|
|
this <- thisNode
|
|
|
|
|
emptySpan "0.5em"
|
|
|
|
|
sectionSpan "normal" [shown, noScriptShown] $ do
|
|
|
|
|
imgButton "edit cons" "/pencil.svg"
|
|
|
|
|
[style_ "width:12px;opacity:0.5"] $
|
|
|
|
|
JS.switchSectionsEverywhere (this, "editable" :: Text)
|
|
|
|
|
sectionSpan "editable" [] $ do
|
|
|
|
|
imgButton "quit editing cons" "/pencil.svg"
|
|
|
|
|
[style_ "width:12px;opacity:0.5"] $
|
|
|
|
|
JS.switchSectionsEverywhere (this, "normal" :: Text)
|
2016-03-19 00:05:01 +03:00
|
|
|
|
listUid <- randomLongUid
|
2016-03-16 15:46:29 +03:00
|
|
|
|
ul_ [uid_ listUid] $
|
2016-03-15 15:35:35 +03:00
|
|
|
|
mapM_ (renderTrait (item^.uid)) (item^.cons)
|
2016-05-13 01:56:17 +03:00
|
|
|
|
section "editable" [] $ do
|
2016-03-15 15:35:35 +03:00
|
|
|
|
smallMarkdownEditor
|
|
|
|
|
[rows_ "3", placeholder_ "add con"]
|
2016-07-24 13:12:17 +03:00
|
|
|
|
(toMarkdownInline "")
|
2016-03-16 15:46:29 +03:00
|
|
|
|
(\val -> JS.addCon (JS.selectUid listUid, item^.uid, val) <>
|
2016-03-15 15:35:35 +03:00
|
|
|
|
JS.assign val ("" :: Text))
|
|
|
|
|
Nothing
|
2016-07-21 22:24:06 +03:00
|
|
|
|
"press Ctrl+Enter or Enter to add"
|
2016-05-13 01:56:17 +03:00
|
|
|
|
textButton "edit off" $
|
|
|
|
|
JS.switchSectionsEverywhere(this, "normal" :: Text)
|
2016-03-15 15:35:35 +03:00
|
|
|
|
|
2016-07-25 19:47:49 +03:00
|
|
|
|
renderTrait :: MonadIO m => Uid Item -> Trait -> HtmlT m ()
|
2016-08-17 11:18:57 +03:00
|
|
|
|
renderTrait itemUid trait =
|
|
|
|
|
mustache "trait" $ A.object [
|
|
|
|
|
"item" A..= A.object [
|
|
|
|
|
"uid" A..= itemUid ],
|
|
|
|
|
"trait" A..= trait ]
|
2016-03-15 15:35:35 +03:00
|
|
|
|
|
|
|
|
|
-- TODO: automatically provide links to modules in Markdown (and have a
|
|
|
|
|
-- database of modules or something)
|
|
|
|
|
|
|
|
|
|
-- TODO: [very-easy] write about the all-is-text extension
|
|
|
|
|
-- TODO: [easy] write that arrows are for arranging stuff, not upvoting
|
|
|
|
|
|
|
|
|
|
-- TODO: [easy] add Hayoo search, Hoogle search, and Hackage search shortcut
|
|
|
|
|
-- boxes
|
|
|
|
|
|
|
|
|
|
-- TODO: when searching, show links to package, main modules, etc before all
|
|
|
|
|
-- categories
|
|
|
|
|
|
|
|
|
|
-- TODO: attach TODOs (“fix grammar”, etc) to items and categories (or should
|
|
|
|
|
-- people instead just write “TODO fix grammar” in description and then such
|
|
|
|
|
-- things could be displayed in gray font and also there'd be an
|
|
|
|
|
-- automatically updated list of TODOs somewhere?)
|
|
|
|
|
|
2016-07-25 19:47:49 +03:00
|
|
|
|
renderItemNotes :: MonadIO m => Category -> Item -> HtmlT m ()
|
2016-05-01 16:28:10 +03:00
|
|
|
|
renderItemNotes category item = cached (CacheItemNotes (item^.uid)) $ do
|
2016-04-20 01:59:29 +03:00
|
|
|
|
-- Don't change this ID, it's used in e.g. 'JS.expandHash'
|
2016-03-15 15:35:35 +03:00
|
|
|
|
let thisId = "item-notes-" <> uidToText (item^.uid)
|
|
|
|
|
this = JS.selectId thisId
|
2016-04-19 20:03:54 +03:00
|
|
|
|
editingSectionUid <- randomLongUid
|
2016-03-17 03:35:56 +03:00
|
|
|
|
div_ [id_ thisId, class_ "item-notes"] $ do
|
2016-07-06 23:50:02 +03:00
|
|
|
|
let notesLink = categoryLink category <> "#" <> thisId
|
2016-04-22 16:18:58 +03:00
|
|
|
|
a_ [href_ notesLink] $
|
|
|
|
|
strong_ "Notes"
|
|
|
|
|
|
2016-07-24 13:12:17 +03:00
|
|
|
|
let renderTree :: Monad m => Forest ([MD.Node], Text) -> HtmlT m ()
|
2016-04-22 16:18:58 +03:00
|
|
|
|
renderTree [] = return ()
|
|
|
|
|
renderTree xs = ul_ $ do
|
|
|
|
|
for_ xs $ \(Node (is, id') children) -> li_ $ do
|
|
|
|
|
let handler = fromJS (JS.expandItemNotes [item^.uid])
|
2016-07-24 13:12:17 +03:00
|
|
|
|
-- The link has to be absolute because sometimes we are
|
|
|
|
|
-- looking at items from pages different from the proper
|
|
|
|
|
-- category pages (e.g. if a search from the main page
|
|
|
|
|
-- returned several items from different categories, and the
|
|
|
|
|
-- user is looking at those items' notes without leaving the
|
|
|
|
|
-- search page). Well, actually it doesn't happen yet because
|
|
|
|
|
-- there's no search (or rather, there is search but it
|
|
|
|
|
-- doesn't return items, only categories); however, it might
|
|
|
|
|
-- start happening and then it's better to be prepared.
|
2016-07-06 23:50:02 +03:00
|
|
|
|
fullLink = categoryLink category <> "#" <> id'
|
2016-04-22 16:18:58 +03:00
|
|
|
|
a_ [href_ fullLink, onclick_ handler] $
|
2016-07-24 13:12:17 +03:00
|
|
|
|
toHtmlRaw (renderMD is)
|
2016-04-22 16:18:58 +03:00
|
|
|
|
renderTree children
|
2016-04-21 19:40:00 +03:00
|
|
|
|
let renderTOC = do
|
2016-04-22 01:06:02 +03:00
|
|
|
|
let toc = item^.notes.mdTOC
|
2016-04-21 19:40:00 +03:00
|
|
|
|
div_ [class_ "notes-toc"] $ do
|
|
|
|
|
if null toc
|
2016-04-22 01:06:02 +03:00
|
|
|
|
then p_ (emptySpan "1.5em" >> "<notes are empty>")
|
2016-04-21 19:40:00 +03:00
|
|
|
|
else renderTree toc
|
|
|
|
|
|
2016-03-15 15:35:35 +03:00
|
|
|
|
section "collapsed" [shown] $ do
|
2016-04-16 02:02:43 +03:00
|
|
|
|
textButton "expand notes" $
|
2016-04-20 01:59:29 +03:00
|
|
|
|
JS.expandItemNotes [item^.uid]
|
2016-04-21 19:40:00 +03:00
|
|
|
|
renderTOC
|
2016-03-15 15:35:35 +03:00
|
|
|
|
|
|
|
|
|
section "expanded" [noScriptShown] $ do
|
2016-04-19 20:03:54 +03:00
|
|
|
|
textareaUid <- randomLongUid
|
2016-04-22 01:06:02 +03:00
|
|
|
|
contents <- if markdownNull (item^.notes)
|
2016-04-19 20:03:54 +03:00
|
|
|
|
then liftIO $ T.readFile "static/item-notes-template.md"
|
|
|
|
|
else return (item^.notes.mdText)
|
2016-03-15 15:35:35 +03:00
|
|
|
|
let buttons = do
|
2016-04-16 02:02:43 +03:00
|
|
|
|
textButton "collapse notes" $
|
2016-03-15 15:35:35 +03:00
|
|
|
|
JS.switchSection (this, "collapsed" :: Text)
|
2016-03-15 15:41:09 +03:00
|
|
|
|
emptySpan "1em"
|
|
|
|
|
textButton "edit notes" $
|
2016-04-22 16:59:50 +03:00
|
|
|
|
-- See Note [dynamic interface]
|
2016-04-19 20:03:54 +03:00
|
|
|
|
JS.makeItemNotesEditor (
|
|
|
|
|
this, JS.selectUid editingSectionUid,
|
|
|
|
|
textareaUid,
|
2016-06-19 19:20:28 +03:00
|
|
|
|
-- See Note [blurb diffing]
|
|
|
|
|
markdownNull (item^.notes),
|
2016-04-19 20:03:54 +03:00
|
|
|
|
contents,
|
|
|
|
|
item^.uid) <>
|
|
|
|
|
JS.switchSection (this, "editing" :: Text) <>
|
2016-07-27 15:33:53 +03:00
|
|
|
|
JS.autosizeTextarea [JS.selectUid textareaUid] <>
|
|
|
|
|
JS.focusOn [JS.selectUid textareaUid]
|
2016-03-15 15:35:35 +03:00
|
|
|
|
buttons
|
2016-04-21 19:40:00 +03:00
|
|
|
|
renderTOC
|
2016-04-21 19:28:35 +03:00
|
|
|
|
div_ [class_ "notes-like"] $ do
|
2016-04-22 01:06:02 +03:00
|
|
|
|
if markdownNull (item^.notes)
|
2016-04-21 19:28:35 +03:00
|
|
|
|
then p_ "add something!"
|
|
|
|
|
else toHtml (item^.notes)
|
2016-04-22 01:06:02 +03:00
|
|
|
|
unless (markdownNull (item^.notes)) $
|
2016-04-21 19:28:35 +03:00
|
|
|
|
buttons
|
2016-03-15 15:35:35 +03:00
|
|
|
|
-- TODO: [easy] the lower “hide notes” should scroll back to item when
|
|
|
|
|
-- the notes are closed (but don't scroll if it's already visible after
|
|
|
|
|
-- the notes have been hidden)
|
|
|
|
|
|
2016-04-19 20:03:54 +03:00
|
|
|
|
section "editing" [uid_ editingSectionUid] $
|
|
|
|
|
return ()
|
2016-03-15 15:35:35 +03:00
|
|
|
|
|
2016-08-17 11:18:57 +03:00
|
|
|
|
renderItemForFeed
|
2016-11-27 14:45:38 +03:00
|
|
|
|
:: (MonadIO m)
|
2016-08-17 11:18:57 +03:00
|
|
|
|
=> Category -> Item -> HtmlT m ()
|
2016-05-22 14:43:46 +03:00
|
|
|
|
renderItemForFeed category item = do
|
2016-03-21 02:12:03 +03:00
|
|
|
|
h1_ $ renderItemTitle item
|
2016-04-22 01:06:02 +03:00
|
|
|
|
unless (markdownNull (item^.description)) $
|
2016-03-19 21:36:21 +03:00
|
|
|
|
toHtml (item^.description)
|
2016-05-22 14:43:46 +03:00
|
|
|
|
when (category^.prosConsEnabled) $ do
|
|
|
|
|
h2_ "Pros"
|
|
|
|
|
ul_ $ mapM_ (p_ . li_ . toHtml . view content) (item^.pros)
|
|
|
|
|
h2_ "Cons"
|
|
|
|
|
ul_ $ mapM_ (p_ . li_ . toHtml . view content) (item^.cons)
|
|
|
|
|
when (category^.ecosystemEnabled) $ do
|
|
|
|
|
unless (markdownNull (item^.ecosystem)) $ do
|
|
|
|
|
h2_ "Ecosystem"
|
|
|
|
|
toHtml (item^.ecosystem)
|
2016-04-22 16:18:58 +03:00
|
|
|
|
-- TODO: include .notes-like style here? otherwise the headers are too big
|
2016-04-22 01:06:02 +03:00
|
|
|
|
unless (markdownNull (item^.notes)) $ do
|
2016-03-19 21:36:21 +03:00
|
|
|
|
h2_ "Notes"
|
|
|
|
|
toHtml (item^.notes)
|
|
|
|
|
|
2016-03-15 15:35:35 +03:00
|
|
|
|
-- Utils
|
|
|
|
|
|
2016-03-22 01:17:53 +03:00
|
|
|
|
onPageLoad :: Monad m => JS -> HtmlT m ()
|
2016-06-12 22:35:13 +03:00
|
|
|
|
onPageLoad js = script_ $ T.format "$(document).ready(function(){{}});" [js]
|
2016-03-15 15:35:35 +03:00
|
|
|
|
|
2016-03-22 01:17:53 +03:00
|
|
|
|
emptySpan :: Monad m => Text -> HtmlT m ()
|
2016-03-15 15:35:35 +03:00
|
|
|
|
emptySpan w = span_ [style_ ("margin-left:" <> w)] mempty
|
|
|
|
|
|
|
|
|
|
-- Use inputValue to get the value (works with input_ and textarea_)
|
|
|
|
|
onEnter :: JS -> Attribute
|
|
|
|
|
onEnter handler = onkeydown_ $
|
2016-07-23 02:33:51 +03:00
|
|
|
|
T.format "if (event.keyCode == 13 || event.keyCode == 10)\
|
2016-07-27 15:05:53 +03:00
|
|
|
|
\ {{} return false;}\n" [handler]
|
2016-03-15 15:35:35 +03:00
|
|
|
|
|
2016-07-21 22:15:15 +03:00
|
|
|
|
onCtrlEnter :: JS -> Attribute
|
|
|
|
|
onCtrlEnter handler = onkeydown_ $
|
2016-07-23 02:33:51 +03:00
|
|
|
|
T.format "if ((event.keyCode == 13 || event.keyCode == 10) &&\
|
|
|
|
|
\ (event.metaKey || event.ctrlKey))\
|
2016-07-27 15:05:53 +03:00
|
|
|
|
\ {{} return false;}\n" [handler]
|
|
|
|
|
|
|
|
|
|
onEscape :: JS -> Attribute
|
|
|
|
|
onEscape handler = onkeydown_ $
|
|
|
|
|
T.format "if (event.keyCode == 27)\
|
|
|
|
|
\ {{} return false;}\n" [handler]
|
2016-07-21 22:15:15 +03:00
|
|
|
|
|
2016-03-22 01:17:53 +03:00
|
|
|
|
textInput :: Monad m => [Attribute] -> HtmlT m ()
|
2016-03-15 15:35:35 +03:00
|
|
|
|
textInput attrs = input_ (type_ "text" : attrs)
|
|
|
|
|
|
|
|
|
|
inputValue :: JS
|
|
|
|
|
inputValue = JS "this.value"
|
|
|
|
|
|
|
|
|
|
clearInput :: JS
|
|
|
|
|
clearInput = JS "this.value = '';"
|
|
|
|
|
|
|
|
|
|
onFormSubmit :: (JS -> JS) -> Attribute
|
2016-06-12 22:35:13 +03:00
|
|
|
|
onFormSubmit f = onsubmit_ $ T.format "{} return false;" [f (JS "this")]
|
2016-03-15 15:35:35 +03:00
|
|
|
|
|
2016-03-22 01:17:53 +03:00
|
|
|
|
button :: Monad m => Text -> [Attribute] -> JS -> HtmlT m ()
|
2016-03-15 15:35:35 +03:00
|
|
|
|
button value attrs handler =
|
|
|
|
|
input_ (type_ "button" : value_ value : onclick_ handler' : attrs)
|
|
|
|
|
where
|
|
|
|
|
handler' = fromJS handler
|
|
|
|
|
|
|
|
|
|
-- A text button looks like “[cancel]”
|
|
|
|
|
textButton
|
2016-03-22 01:17:53 +03:00
|
|
|
|
:: Monad m
|
|
|
|
|
=> Text -- ^ Button text
|
2016-03-15 15:35:35 +03:00
|
|
|
|
-> JS -- ^ Onclick handler
|
2016-03-22 01:17:53 +03:00
|
|
|
|
-> HtmlT m ()
|
2016-03-15 15:35:35 +03:00
|
|
|
|
textButton caption (JS handler) =
|
|
|
|
|
span_ [class_ "text-button"] $
|
|
|
|
|
-- “#” is used instead of javascript:void(0) because the latter is slow
|
|
|
|
|
-- in Firefox (at least for me – tested with Firefox 43 on Arch Linux)
|
|
|
|
|
a_ [href_ "#", onclick_ (handler <> "return false;")]
|
|
|
|
|
(toHtml caption)
|
|
|
|
|
|
|
|
|
|
-- So far all icons used here have been from <https://useiconic.com/open/>
|
2016-03-22 01:17:53 +03:00
|
|
|
|
imgButton :: Monad m => Text -> Url -> [Attribute] -> JS -> HtmlT m ()
|
2016-03-15 15:35:35 +03:00
|
|
|
|
imgButton alt src attrs (JS handler) =
|
|
|
|
|
a_ [href_ "#", onclick_ (handler <> "return false;")]
|
2016-03-22 20:20:34 +03:00
|
|
|
|
(img_ (src_ src : alt_ alt : title_ alt : attrs))
|
2016-03-15 15:35:35 +03:00
|
|
|
|
|
2016-05-03 03:27:30 +03:00
|
|
|
|
mkLink :: Monad m => HtmlT m a -> Url -> HtmlT m a
|
|
|
|
|
mkLink x src = a_ [href_ src] x
|
|
|
|
|
|
2016-05-05 16:50:10 +03:00
|
|
|
|
selectedIf :: With w => Bool -> w -> w
|
|
|
|
|
selectedIf p x = if p then with x [selected_ "selected"] else x
|
|
|
|
|
|
2016-05-22 14:43:46 +03:00
|
|
|
|
checkedIf :: With w => Bool -> w -> w
|
|
|
|
|
checkedIf p x = if p then with x [checked_] else x
|
|
|
|
|
|
|
|
|
|
hiddenIf :: With w => Bool -> w -> w
|
|
|
|
|
hiddenIf p x = if p then with x [style_ "display:none;"] else x
|
|
|
|
|
|
2016-03-15 15:35:35 +03:00
|
|
|
|
markdownEditor
|
2016-07-25 19:47:49 +03:00
|
|
|
|
:: MonadIO m
|
2016-03-22 01:17:53 +03:00
|
|
|
|
=> [Attribute]
|
2016-03-17 15:29:45 +03:00
|
|
|
|
-> MarkdownBlock -- ^ Default text
|
2016-03-16 02:17:08 +03:00
|
|
|
|
-> (JS -> JS) -- ^ “Submit” handler, receiving the contents of the editor
|
|
|
|
|
-> JS -- ^ “Cancel” handler
|
2016-07-21 22:15:15 +03:00
|
|
|
|
-> Text -- ^ Instruction (e.g. “press Ctrl+Enter to save”)
|
2016-03-22 01:17:53 +03:00
|
|
|
|
-> HtmlT m ()
|
2016-07-21 22:15:15 +03:00
|
|
|
|
markdownEditor attr (view mdText -> s) submit cancel instr = do
|
2016-03-24 03:02:09 +03:00
|
|
|
|
textareaUid <- randomLongUid
|
2016-07-21 22:15:15 +03:00
|
|
|
|
let val = JS $ T.format "document.getElementById(\"{}\").value" [textareaUid]
|
2016-03-15 15:35:35 +03:00
|
|
|
|
-- Autocomplete has to be turned off thanks to
|
|
|
|
|
-- <http://stackoverflow.com/q/8311455>.
|
2016-07-21 22:15:15 +03:00
|
|
|
|
textarea_ ([uid_ textareaUid,
|
|
|
|
|
autocomplete_ "off",
|
|
|
|
|
class_ "big fullwidth",
|
2016-07-27 15:05:53 +03:00
|
|
|
|
onCtrlEnter (submit val),
|
|
|
|
|
onEscape (JS.assign val s <> cancel) ]
|
2016-03-17 15:29:45 +03:00
|
|
|
|
++ attr) $
|
2016-03-15 15:35:35 +03:00
|
|
|
|
toHtml s
|
2016-09-11 21:56:52 +03:00
|
|
|
|
button "Save" [class_ " save "] $
|
2016-03-15 15:35:35 +03:00
|
|
|
|
submit val
|
|
|
|
|
emptySpan "6px"
|
2016-09-11 21:56:52 +03:00
|
|
|
|
button "Cancel" [class_ " cancel "] $
|
2016-03-15 15:35:35 +03:00
|
|
|
|
JS.assign val s <>
|
|
|
|
|
cancel
|
|
|
|
|
emptySpan "6px"
|
2016-07-21 22:15:15 +03:00
|
|
|
|
span_ [class_ "edit-field-instruction"] (toHtml instr)
|
2016-10-08 11:27:01 +03:00
|
|
|
|
a_ [href_ "/markdown", target_ "_blank"] $
|
|
|
|
|
img_ [src_ "/markdown.svg", alt_ "markdown supported", class_ " markdown-supported "]
|
2016-03-15 15:35:35 +03:00
|
|
|
|
|
|
|
|
|
smallMarkdownEditor
|
2016-07-25 19:47:49 +03:00
|
|
|
|
:: MonadIO m
|
2016-03-22 01:17:53 +03:00
|
|
|
|
=> [Attribute]
|
2016-03-16 02:17:08 +03:00
|
|
|
|
-> MarkdownInline -- ^ Default text
|
|
|
|
|
-> (JS -> JS) -- ^ “Submit” handler, receiving the contents of the editor
|
|
|
|
|
-> Maybe JS -- ^ “Cancel” handler (if “Cancel” is needed)
|
2016-07-21 22:15:15 +03:00
|
|
|
|
-> Text -- ^ Instruction (e.g. “press Enter to add”)
|
2016-03-22 01:17:53 +03:00
|
|
|
|
-> HtmlT m ()
|
2016-07-21 22:15:15 +03:00
|
|
|
|
smallMarkdownEditor attr (view mdText -> s) submit mbCancel instr = do
|
2016-03-19 00:05:01 +03:00
|
|
|
|
textareaId <- randomLongUid
|
2016-06-12 22:35:13 +03:00
|
|
|
|
let val = JS $ T.format "document.getElementById(\"{}\").value" [textareaId]
|
2016-07-27 15:05:53 +03:00
|
|
|
|
textarea_ ([class_ "fullwidth", uid_ textareaId, autocomplete_ "off"] ++
|
|
|
|
|
[onEnter (submit val)] ++
|
|
|
|
|
[onEscape cancel | Just cancel <- [mbCancel]] ++
|
|
|
|
|
attr) $
|
2016-03-15 15:35:35 +03:00
|
|
|
|
toHtml s
|
2016-07-21 20:46:16 +03:00
|
|
|
|
br_ []
|
|
|
|
|
for_ mbCancel $ \cancel -> do
|
|
|
|
|
textButton "cancel" $
|
|
|
|
|
JS.assign val s <>
|
|
|
|
|
cancel
|
|
|
|
|
span_ [style_ "float:right"] $ do
|
2016-07-21 22:15:15 +03:00
|
|
|
|
span_ [class_ "edit-field-instruction"] (toHtml instr)
|
2016-10-08 11:27:01 +03:00
|
|
|
|
a_ [href_ "/markdown", target_ "_blank"] $
|
|
|
|
|
img_ [src_ "/markdown.svg", alt_ "markdown supported", class_ " markdown-supported "]
|
2016-03-15 15:35:35 +03:00
|
|
|
|
|
2016-07-25 19:47:49 +03:00
|
|
|
|
thisNode :: MonadIO m => HtmlT m JQuerySelector
|
2016-03-15 15:35:35 +03:00
|
|
|
|
thisNode = do
|
2016-03-19 00:05:01 +03:00
|
|
|
|
uid' <- randomLongUid
|
2016-03-15 15:35:35 +03:00
|
|
|
|
-- If the class name ever changes, fix 'JS.moveNodeUp' and
|
|
|
|
|
-- 'JS.moveNodeDown'.
|
|
|
|
|
span_ [uid_ uid', class_ "dummy"] mempty
|
|
|
|
|
return (JS.selectParent (JS.selectUid uid'))
|
|
|
|
|
|
2016-04-07 15:54:11 +03:00
|
|
|
|
itemNodeId :: Item -> Text
|
|
|
|
|
itemNodeId item = "item-" <> uidToText (item^.uid)
|
|
|
|
|
|
|
|
|
|
categoryNodeId :: Category -> Text
|
|
|
|
|
categoryNodeId category = "category-" <> uidToText (category^.uid)
|
|
|
|
|
|
2016-07-06 23:50:02 +03:00
|
|
|
|
-- TODO: another absolute link to get rid of [absolute-links]
|
|
|
|
|
categoryLink :: Category -> Url
|
|
|
|
|
categoryLink category = "/haskell/" <> categorySlug category
|
|
|
|
|
|
|
|
|
|
itemLink :: Category -> Item -> Url
|
2016-04-22 01:06:02 +03:00
|
|
|
|
itemLink category item =
|
2016-06-12 22:35:13 +03:00
|
|
|
|
T.format "/haskell/{}#{}" (categorySlug category, itemNodeId item)
|
2016-04-22 01:06:02 +03:00
|
|
|
|
|
2016-03-27 02:34:07 +03:00
|
|
|
|
-- See Note [show-hide]; wheh changing these, also look at 'JS.switchSection'.
|
2016-03-15 15:35:35 +03:00
|
|
|
|
shown, noScriptShown :: Attribute
|
|
|
|
|
shown = class_ " shown "
|
|
|
|
|
noScriptShown = class_ " noscript-shown "
|
|
|
|
|
|
2016-03-27 02:34:07 +03:00
|
|
|
|
-- See Note [show-hide]
|
|
|
|
|
section
|
|
|
|
|
:: Monad m
|
2016-04-11 23:31:30 +03:00
|
|
|
|
=> Text -- ^ Section name (or names)
|
2016-03-27 02:34:07 +03:00
|
|
|
|
-> [Attribute] -- ^ Additional attributes
|
|
|
|
|
-> HtmlT m () -- ^ Content of the section
|
|
|
|
|
-> HtmlT m ()
|
2016-03-15 15:35:35 +03:00
|
|
|
|
section t attrs = div_ (class_ (t <> " section ") : attrs)
|
|
|
|
|
|
2016-03-27 02:34:07 +03:00
|
|
|
|
-- See Note [show-hide]
|
|
|
|
|
sectionSpan
|
|
|
|
|
:: Monad m
|
2016-04-11 23:31:30 +03:00
|
|
|
|
=> Text -- ^ Section name (or names)
|
2016-03-27 02:34:07 +03:00
|
|
|
|
-> [Attribute] -- ^ Additional attributes
|
|
|
|
|
-> HtmlT m () -- ^ Content of the section
|
|
|
|
|
-> HtmlT m ()
|
2016-03-15 15:35:35 +03:00
|
|
|
|
sectionSpan t attrs = span_ (class_ (t <> " section ") : attrs)
|
|
|
|
|
|
2016-08-19 04:07:45 +03:00
|
|
|
|
{-
|
2016-10-20 18:54:20 +03:00
|
|
|
|
TODO: warn about how one shouldn't write @foo("{{bar}}")@ in templates,
|
|
|
|
|
because a newline in 'bar' directly after the quote will mess things
|
|
|
|
|
up. Write @foo({{{%js bar}}})@ instead.
|
2016-08-19 04:07:45 +03:00
|
|
|
|
-}
|
2016-08-17 11:18:57 +03:00
|
|
|
|
mustache :: MonadIO m => PName -> A.Value -> HtmlT m ()
|
|
|
|
|
mustache f v = do
|
|
|
|
|
let functions = M.fromList [
|
|
|
|
|
("selectIf", \[x] -> if x == A.Bool True
|
|
|
|
|
then return (A.String "selected")
|
|
|
|
|
else return A.Null),
|
2016-08-19 04:07:45 +03:00
|
|
|
|
("js", \[x] -> return $
|
|
|
|
|
A.String . T.toStrict . TL.decodeUtf8 . A.encode $ x),
|
2016-08-17 11:18:57 +03:00
|
|
|
|
("trace", \xs -> do
|
|
|
|
|
mapM_ (BS.putStrLn . A.encodePretty) xs
|
|
|
|
|
return A.Null) ]
|
|
|
|
|
widgets <- readWidgets
|
|
|
|
|
let templates = [(tname, t) | (HTML_ tname, t) <- widgets]
|
|
|
|
|
when (null templates) $
|
|
|
|
|
error "View.mustache: no HTML templates found in templates/"
|
|
|
|
|
parsed <- for templates $ \(tname, t) -> do
|
|
|
|
|
let pname = fromString (T.unpack tname)
|
|
|
|
|
case compileMustacheText pname (T.toLazy t) of
|
|
|
|
|
Left e -> error $ printf "View.mustache: when parsing %s: %s"
|
|
|
|
|
tname (parseErrorPretty e)
|
|
|
|
|
Right template -> return template
|
|
|
|
|
let combined = (Semigroup.sconcat (NonEmpty.fromList parsed)) {
|
|
|
|
|
templateActual = f }
|
|
|
|
|
(rendered, warnings) <- liftIO $ renderMustacheM functions combined v
|
|
|
|
|
when (not (null warnings)) $
|
|
|
|
|
error $ printf "View.mustache: warnings when rendering %s:\n%s"
|
|
|
|
|
(unPName f) (unlines warnings)
|
|
|
|
|
toHtmlRaw rendered
|
|
|
|
|
|
|
|
|
|
data SectionType
|
|
|
|
|
= HTML_ Text | JS_ | CSS_ | Description_ | Note_ Text
|
|
|
|
|
|
|
|
|
|
-- | Used to turn collected section lines back into a section.
|
|
|
|
|
--
|
|
|
|
|
-- * Trims surrounding blank lines
|
|
|
|
|
-- * Doesn't append a newline when there's only one line
|
|
|
|
|
-- (useful for inline partials)
|
|
|
|
|
unlinesSection :: [Text] -> Text
|
|
|
|
|
unlinesSection = unlines' . dropWhile T.null . dropWhileEnd T.null
|
|
|
|
|
where
|
|
|
|
|
unlines' [] = ""
|
|
|
|
|
unlines' [x] = x
|
|
|
|
|
unlines' xs = T.unlines xs
|
|
|
|
|
|
|
|
|
|
readWidget :: MonadIO m => FilePath -> m [(SectionType, Text)]
|
|
|
|
|
readWidget fp = liftIO $ do
|
|
|
|
|
s <- T.readFile fp
|
|
|
|
|
let isDivide line = (T.all (== '=') line || T.all (== '-') line) &&
|
|
|
|
|
T.length line >= 20
|
|
|
|
|
let go (x:y:[]) = [(T.strip (last x), unlinesSection y)]
|
|
|
|
|
go (x:y:xs) = (T.strip (last x), unlinesSection (init y)) : go (y : xs)
|
|
|
|
|
go _ = error $ "View.readWidget: couldn't read " ++ fp
|
|
|
|
|
let sections = go (splitWhen isDivide (T.lines s))
|
|
|
|
|
let sectionTypeP :: Parser SectionType
|
|
|
|
|
sectionTypeP = choice [
|
|
|
|
|
do string "HTML"
|
|
|
|
|
HTML_ <$> choice [
|
|
|
|
|
string ": " >> (T.pack <$> some anyChar),
|
|
|
|
|
return (T.pack (takeBaseName fp)) ],
|
|
|
|
|
string "JS" $> JS_,
|
|
|
|
|
string "CSS" $> CSS_,
|
|
|
|
|
string "Description" $> Description_,
|
|
|
|
|
do string "Note ["
|
|
|
|
|
Note_ . T.pack <$> someTill anyChar (char ']') ]
|
|
|
|
|
let parseSectionType t = case parse (sectionTypeP <* eof) fp t of
|
|
|
|
|
Right x -> x
|
|
|
|
|
Left e -> error $ printf "invalid section name: '%s'\n%s"
|
|
|
|
|
t (parseErrorPretty e)
|
|
|
|
|
return $ over (each._1) parseSectionType sections
|
|
|
|
|
|
|
|
|
|
readWidgets :: MonadIO m => m [(SectionType, Text)]
|
|
|
|
|
readWidgets = liftIO $ do
|
|
|
|
|
let isWidget = F.extension F.==? ".widget"
|
|
|
|
|
files <- F.find F.always isWidget "templates/"
|
|
|
|
|
concat <$> mapM readWidget files
|
|
|
|
|
|
|
|
|
|
getJS :: MonadIO m => m Text
|
|
|
|
|
getJS = do
|
|
|
|
|
widgets <- readWidgets
|
|
|
|
|
let js = [t | (JS_, t) <- widgets]
|
|
|
|
|
return (T.concat js)
|
|
|
|
|
|
|
|
|
|
getCSS :: MonadIO m => m Text
|
|
|
|
|
getCSS = do
|
|
|
|
|
widgets <- readWidgets
|
|
|
|
|
let css = [t | (CSS_, t) <- widgets]
|
|
|
|
|
return (T.concat css)
|