1
1
mirror of https://github.com/aelve/guide.git synced 2024-11-23 21:13:07 +03:00
guide/src/View.hs

1119 lines
42 KiB
Haskell
Raw Normal View History

2016-03-15 15:35:35 +03:00
{-# LANGUAGE
QuasiQuotes,
OverloadedStrings,
FlexibleContexts,
ViewPatterns,
2016-04-07 22:14:08 +03:00
RecordWildCards,
2016-04-15 14:14:01 +03:00
TupleSections,
2016-03-15 15:35:35 +03:00
NoImplicitPrelude
#-}
module View
(
-- * Pages
renderRoot,
2016-04-07 22:14:08 +03:00
renderAdmin,
2016-04-15 14:14:01 +03:00
renderEdits,
renderHaskellRoot,
2016-03-15 15:35:35 +03:00
renderDonate,
2016-03-19 02:40:00 +03:00
renderCategoryPage,
2016-03-20 13:50:23 +03:00
renderUnwrittenRules,
2016-03-15 15:35:35 +03:00
-- * Tracking
renderTracking,
-- * Methods
renderHelp,
-- ** Categories
renderCategoryList,
renderCategory,
renderCategoryTitle,
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,
newGroupValue,
)
where
-- General
import BasePrelude hiding (Category)
2016-04-16 02:02:43 +03:00
-- Default
import Data.Default
2016-03-15 15:35:35 +03:00
-- Lenses
import Lens.Micro.Platform hiding ((&))
-- Monads and monad transformers
import Control.Monad.IO.Class
import Control.Monad.Reader
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
import qualified Data.Text as T
import qualified Data.Text.IO as T
import Data.Text (Text)
import NeatInterpolation
-- Web
import Lucid hiding (for_)
2016-04-07 22:14:08 +03:00
-- Time
import Data.Time.Format.Human
2016-04-16 02:02:43 +03:00
-- Markdown
import Cheapskate.Lucid
import Cheapskate.Types
2016-03-15 15:35:35 +03:00
-- Local
import Config
2016-03-15 15:35:35 +03:00
import Types
import Utils
import JS (JS(..), JQuerySelector)
import qualified JS
import Markdown
{- Note [autosize]
~~~~~~~~~~~~~~~~~~
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:
autosize($('textarea'));
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.
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).
In switchSection we use
autosize($('textarea'));
autosize.update($('textarea'));
instead of simple
autosize.update($('textarea'));
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-27 02:34:07 +03:00
{- Note [show-hide]
~~~~~~~~~~~~~~~~~~~
A lot of things (help, 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.
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>).
section "normal" [shown, noScriptShown] $ do
renderText
...
section "editing" [] $ do
renderEditbox
...
2016-04-11 23:31:30 +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-03-27 02:34:07 +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.)
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.
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-04-11 23:31:30 +03:00
////////////////////////////////////
2016-03-27 02:34:07 +03:00
And now, here's how it's all implemented.
In 'wrapPage' there's a piece of CSS wrapped in <noscript> that hides everything except for 'noScriptShown' things:
.section:not(.noscript-shown) {display:none;}
There's also a piece of Javascript that, when executed, will change it to the following CSS:
.section:not(.shown) {display:none;}
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.
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.)
-}
renderRoot :: (MonadIO m, MonadReader Config m) => HtmlT m ()
renderRoot = do
wrapPage "Aelve Guide" $ do
h1_ "Aelve Guide"
h2_ (a_ [href_ "/haskell"] "Haskell")
2016-04-07 22:14:08 +03:00
-- TODO: show a “category not found” page
renderAdmin :: MonadIO m => GlobalState -> [(Edit, EditDetails)] -> HtmlT m ()
renderAdmin globalState edits = do
2016-04-08 18:05:52 +03:00
head_ $ do
includeJS "/js.js"
includeJS "/jquery-2.2.0.min.js"
includeCSS "/markup.css"
2016-04-14 01:56:13 +03:00
includeCSS "/admin.css"
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
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-04-13 18:38:35 +03:00
h1_ "Pending edits"
2016-04-15 14:14:01 +03:00
renderEdits globalState (map (,Nothing) edits)
2016-04-07 22:14:08 +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
:: MonadIO m
=> GlobalState
-> [((Edit, EditDetails), Maybe String)]
-> HtmlT m ()
renderEdits globalState edits = do
let editBlocks = groupBy (equating (editIP . snd . fst)) edits
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)
ul_ $ do
for_ editBlock $ \((edit, EditDetails{..}), mbErr) -> li_ $ do
editNode <- thisNode
p_ $ do
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
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)
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)
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))
trait = fromMaybe err (find (hasUid traitId) (getTraits item))
2016-04-07 22:14:08 +03:00
let printCategory catId = do
let category = findCategory catId
quote $ toHtml (category ^. title)
let printItem itemId = do
let (_, item) = findItem itemId
quote $ toHtml (item ^. name)
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-04-14 01:56:13 +03:00
blockquote_ $ p_ $ toHtml (renderMarkdownInline content')
2016-04-07 22:14:08 +03:00
Edit'AddCon itemId _traitId content' -> do
p_ $ "added con to item " >> printItem itemId
2016-04-14 01:56:13 +03:00
blockquote_ $ p_ $ toHtml (renderMarkdownInline 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)
Edit'SetCategoryNotes catId oldNotes newNotes -> do
p_ $ "changed notes of category " >> printCategory catId
table_ $ tr_ $ do
2016-04-14 01:56:13 +03:00
td_ $ blockquote_ $ toHtml (renderMarkdownBlock oldNotes)
td_ $ blockquote_ $ toHtml (renderMarkdownBlock newNotes)
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
p_ $ "changed description of item " >> printItem itemId
table_ $ tr_ $ do
2016-04-14 01:56:13 +03:00
td_ $ blockquote_ $ toHtml (renderMarkdownBlock oldDescr)
td_ $ blockquote_ $ toHtml (renderMarkdownBlock newDescr)
2016-04-07 22:14:08 +03:00
Edit'SetItemNotes itemId oldNotes newNotes -> do
p_ $ "changed notes of item " >> printItem itemId
table_ $ tr_ $ do
2016-04-14 01:56:13 +03:00
td_ $ blockquote_ $ toHtml (renderMarkdownBlock oldNotes)
td_ $ blockquote_ $ toHtml (renderMarkdownBlock newNotes)
2016-04-07 22:14:08 +03:00
Edit'SetItemEcosystem itemId oldEcosystem newEcosystem -> do
p_ $ "changed ecosystem of item " >> printItem itemId
table_ $ tr_ $ do
2016-04-14 01:56:13 +03:00
td_ $ blockquote_ $ toHtml (renderMarkdownBlock oldEcosystem)
td_ $ blockquote_ $ toHtml (renderMarkdownBlock newEcosystem)
2016-04-07 22:14:08 +03:00
-- Change trait properties
Edit'SetTraitContent itemId _traitId oldContent newContent -> do
p_ $ "changed trait of item " >> printItem itemId
table_ $ tr_ $ do
2016-04-14 01:56:13 +03:00
td_ $ blockquote_ $ p_ (toHtml (renderMarkdownInline oldContent))
td_ $ blockquote_ $ p_ (toHtml (renderMarkdownInline 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
renderHaskellRoot
:: (MonadIO m, MonadReader Config m)
=> GlobalState -> Maybe Text -> HtmlT m ()
renderHaskellRoot globalState mbSearchQuery =
2016-03-19 02:40:00 +03:00
wrapPage "Aelve Guide" $ do
onPageLoad $ JS.expandHash ()
-- TODO: [very-easy] this header looks bad when the page is narrow, it
-- should be fixed in css.css by adding line-height to it
case mbSearchQuery of
Nothing -> h1_ "The Haskeller's guide"
-- A search page isn't the main page, so we need a link to the main page
Just _ -> h1_ (a_ [href_ "/haskell"] "The Haskeller's guide")
2016-04-06 01:36:55 +03:00
renderNoScriptWarning
2016-03-15 15:35:35 +03:00
renderHelp
form_ $ do
input_ [type_ "text", name_ "q", id_ "search", placeholder_ "search",
value_ (fromMaybe "" mbSearchQuery)]
textInput [
placeholder_ "add a category",
autocomplete_ "off",
onEnter $ JS.addCategory (JS.selectId "categories", inputValue) <>
clearInput ]
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
renderCategoryList rankedCategories
-- TODO: maybe add a button like “give me random category that is
-- unfinished”
renderCategoryPage
:: (MonadIO m, MonadReader Config m) => Category -> HtmlT m ()
renderCategoryPage category =
wrapPage (category^.title <> " Aelve Guide") $ do
onPageLoad $ JS.expandHash ()
-- TODO: [very-easy] this header looks bad when the page is narrow, it
-- should be fixed in css.css by adding line-height to it
-- TODO: another absolute link [absolute-links]
h1_ (a_ [href_ "/haskell"] "The Haskeller's guide")
2016-04-06 01:36:55 +03:00
renderNoScriptWarning
renderHelp
renderCategory category
2016-04-06 01:36:55 +03:00
renderNoScriptWarning :: MonadIO m => HtmlT m ()
renderNoScriptWarning =
noscript_ $ div_ [id_ "noscript-message"] $
toHtml $ renderMarkdownBlock [text|
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.
|]
renderTracking :: (MonadIO m, MonadReader Config m) => HtmlT m ()
2016-03-15 15:35:35 +03:00
renderTracking = do
trackingEnabled <- lift (asks _trackingEnabled)
when trackingEnabled $ do
tracking <- liftIO $ T.readFile "static/tracking.html"
toHtmlRaw tracking
2016-03-15 15:35:35 +03:00
renderDonate :: (MonadIO m, MonadReader Config m) => HtmlT m ()
renderDonate = wrapPage "Donate to Artyom" $ do
toHtmlRaw =<< liftIO (readFile "static/donate.html")
2016-03-15 15:35:35 +03:00
renderUnwrittenRules :: (MonadIO m, MonadReader Config m) => HtmlT m ()
2016-03-20 13:50:23 +03:00
renderUnwrittenRules = wrapPage "Unwritten rules" $ do
toHtml . renderMarkdownBlock =<<
liftIO (T.readFile "static/unwritten-rules.md")
2016-03-19 02:40:00 +03:00
-- Include all the necessary things
wrapPage
:: (MonadIO m, MonadReader Config m)
=> 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)
meta_ [name_ "viewport",
content_ "width=device-width, initial-scale=1.0, user-scalable=yes"]
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; };
|]
includeJS "/jquery-2.2.0.min.js"
2016-03-19 02:40:00 +03:00
-- See Note [autosize]
includeJS "/autosize-3.0.15.min.js"
2016-03-19 02:40:00 +03:00
onPageLoad (JS "autosize($('textarea'));")
-- 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"
includeCSS "/markup.css"
2016-03-19 02:40:00 +03:00
includeCSS "/css.css"
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"
renderTracking
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
script_ $ fromJS $ JS.createAjaxIndicator ()
div_ [id_ "main"] $
page
2016-03-19 02:40:00 +03:00
div_ [id_ "footer"] $ do
"made by " >> a_ [href_ "https://artyom.me"] "Artyom"
emptySpan "2em"
a_ [href_ "https://github.com/aelve/guide"] "source"
emptySpan "2em"
a_ [href_ "https://github.com/aelve/guide/issues"] "report an issue"
emptySpan "2em"
a_ [href_ "/donate"] "donate"
sup_ [style_ "font-size:50%"] "I don't have a job"
2016-03-15 15:35:35 +03:00
-- TODO: allow archiving items if they are in every way worse than the rest,
-- or something (but searching should still be possible)
-- TODO: add a list for “interesting libraries, but too lazy to describe, so
-- somebody describe them for me”
renderHelp :: (MonadIO m, MonadReader Config m) => HtmlT m ()
2016-03-15 15:35:35 +03:00
renderHelp = do
div_ [id_ "help"] $ do
-- If you're going to change section names, look at 'JS.showHelp' and
-- 'JS.hideHelp'
section "collapsed" [shown] $ do
textButton "show help" $
JS.showHelp (JS.selectId "help", helpVersion)
section "expanded" [noScriptShown] $ do
textButton "hide help" $
JS.hideHelp (JS.selectId "help", helpVersion)
-- Don't forget to change 'helpVersion' when the text changes
-- substantially and you think the users should reread it
help <- liftIO $ T.readFile "static/help.md"
toHtml $ renderMarkdownBlock help
2016-03-20 14:08:26 +03:00
-- Replicating “hide help” so that it would be more noticeable
p_ $ do
let handler =
fromJS (JS.hideHelp (JS.selectId "help", helpVersion)) <>
"return false;"
"If you're finished reading, "
a_ [href_ "#", onclick_ handler] "hide this message"
"."
2016-03-15 15:35:35 +03:00
2016-03-20 14:11:42 +03:00
onPageLoad $ JS.showOrHideHelp (JS.selectId "help", helpVersion)
2016-03-15 15:35:35 +03:00
helpVersion :: Int
2016-03-20 13:50:23 +03:00
helpVersion = 3
2016-03-15 15:35:35 +03:00
renderCategoryList :: MonadIO m => [Category] -> HtmlT m ()
2016-03-15 15:35:35 +03:00
renderCategoryList cats =
div_ [id_ "categories"] $
mapM_ renderCategory cats
renderCategoryTitle :: Monad m => Category -> HtmlT m ()
2016-03-15 15:35:35 +03:00
renderCategoryTitle category = do
let thisId = "category-title-" <> uidToText (category^.uid)
this = JS.selectId thisId
2016-03-22 20:19:05 +03:00
h2_ [id_ thisId, class_ "category-title"] $ do
-- TODO: this link shouldn't be absolute [absolute-links]
span_ [class_ "controls"] $
a_ [href_ ("/haskell/feed/category/" <> uidToText (category^.uid))] $
2016-03-22 20:20:34 +03:00
img_ [src_ "/rss-alt.svg",
alt_ "category feed", title_ "category feed"]
2016-03-22 20:19:05 +03:00
2016-03-15 15:35:35 +03:00
sectionSpan "normal" [shown, noScriptShown] $ do
-- TODO: this link shouldn't be absolute [absolute-links]
a_ [href_ ("/haskell/" <> categorySlug category)] $
2016-03-19 02:40:00 +03:00
toHtml (category^.title)
2016-03-15 15:35:35 +03:00
emptySpan "1em"
textButton "edit" $
JS.switchSection (this, "editing" :: Text)
2016-04-07 15:54:11 +03:00
emptySpan "1em"
-- TODO: when on the category page, deleting the category should
-- redirect to the main page
textButton "delete" $
JS.deleteCategory (category^.uid, categoryNode category)
2016-03-15 15:35:35 +03:00
sectionSpan "editing" [] $ do
textInput [
value_ (category^.title),
autocomplete_ "off",
onEnter $
JS.submitCategoryTitle (this, category^.uid, inputValue)]
emptySpan "1em"
textButton "cancel" $
JS.switchSection (this, "normal" :: Text)
renderCategoryNotes :: MonadIO m => Category -> HtmlT m ()
2016-03-15 15:35:35 +03:00
renderCategoryNotes category = do
let thisId = "category-notes-" <> uidToText (category^.uid)
this = JS.selectId thisId
div_ [id_ thisId] $ do
section "normal" [shown, noScriptShown] $ do
if category^.notes == ""
2016-03-15 15:35:35 +03:00
then p_ "write something here!"
else toHtml (category^.notes)
2016-03-15 15:35:35 +03:00
textButton "edit description" $
JS.switchSection (this, "editing" :: Text)
2016-04-15 16:15:02 +03:00
section "editing" [] $ do
contents <- if category^.notes == ""
then liftIO $ renderMarkdownBlock <$>
T.readFile "static/category-notes-template.md"
else return (category^.notes)
2016-03-15 15:35:35 +03:00
markdownEditor
[rows_ "10"]
2016-04-15 16:15:02 +03:00
contents
2016-03-15 15:35:35 +03:00
(\val -> JS.submitCategoryNotes (this, category^.uid, val))
(JS.switchSection (this, "normal" :: Text))
renderCategory :: MonadIO m => Category -> HtmlT m ()
2016-03-15 15:35:35 +03:00
renderCategory category =
2016-04-07 15:54:11 +03:00
div_ [class_ "category", id_ (categoryNodeId category)] $ do
2016-03-15 15:35:35 +03:00
renderCategoryTitle category
renderCategoryNotes category
itemsNode <- div_ [class_ "items"] $ do
mapM_ (renderItem category) (category^.items)
thisNode
textInput [
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)
-- TODO: perhaps use jQuery Touch Punch or something to allow dragging items
-- instead of using arrows? Touch Punch works on mobile, too
renderItem :: MonadIO m => Category -> Item -> HtmlT m ()
2016-03-17 03:35:56 +03:00
renderItem category item =
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
2016-03-15 15:35:35 +03:00
-- TODO: replace “edit description” with a big half-transparent pencil
-- to the left of it
2016-03-17 03:35:56 +03:00
let bg = hueToLightColor $ getItemHue category item
div_ [class_ "item-body", style_ ("background-color:" <> bg)] $ do
renderItemDescription item
renderItemTraits item
2016-03-17 14:58:44 +03:00
renderItemEcosystem item
2016-03-17 03:35:56 +03:00
-- TODO: add a separator here? [very-easy]
renderItemNotes 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-03-21 02:12:03 +03:00
renderItemTitle :: Monad m => Item -> HtmlT m ()
renderItemTitle item = do
2016-03-19 21:36:21 +03:00
let hackageLink x = "https://hackage.haskell.org/package/" <> x
case item^.kind of
-- If the library is on Hackage, the title links to its Hackage
-- page; otherwise, it doesn't link anywhere. Even if the link
-- field is present, it's going to be rendered as “(site)”, not
-- linked in the title.
Library hackageName' -> do
case hackageName' of
Just x -> a_ [href_ (hackageLink x)] (toHtml (item^.name))
Nothing -> toHtml (item^.name)
case item^.link of
Just l -> " (" >> a_ [href_ l] "site" >> ")"
Nothing -> return ()
-- For tools, it's the opposite the title links to the item site
-- (if present), and there's a separate “(Hackage)” link if the
-- tool is on Hackage.
Tool hackageName' -> do
case item^.link of
Just l -> a_ [href_ l] (toHtml (item^.name))
Nothing -> toHtml (item^.name)
case hackageName' of
Just x -> " (" >> a_ [href_ (hackageLink x)] "Hackage" >> ")"
Nothing -> return ()
-- And now everything else
Other -> do
case item^.link of
Just l -> a_ [href_ l] (toHtml (item^.name))
Nothing -> toHtml (item^.name)
2016-03-15 15:35:35 +03:00
-- TODO: give a link to oldest available docs when the new docs aren't there
renderItemInfo :: MonadIO m => Category -> Item -> HtmlT m ()
2016-03-15 15:35:35 +03:00
renderItemInfo cat item = do
let bg = hueToDarkColor $ getItemHue cat item
let thisId = "item-info-" <> uidToText (item^.uid)
this = JS.selectId thisId
div_ [id_ thisId, class_ "item-info",
style_ ("background-color:" <> bg)] $ do
section "normal" [shown, noScriptShown] $ do
-- TODO: [very-easy] move this style_ into css.css
span_ [style_ "font-size:150%"] $ do
2016-03-20 13:30:10 +03:00
-- TODO: absolute links again [absolute-links]
2016-04-07 15:54:11 +03:00
let link' = format "/haskell/{}#{}" (categorySlug cat, itemNodeId item)
2016-03-20 13:30:10 +03:00
a_ [class_ "anchor", href_ link'] "#"
2016-03-21 02:12:03 +03:00
renderItemTitle item
2016-03-15 15:35:35 +03:00
emptySpan "2em"
toHtml (fromMaybe "other" (item^.group_))
span_ [class_ "controls"] $ do
imgButton "move item up" "/arrow-thick-top.svg" [] $
2016-04-07 15:54:11 +03:00
JS.moveItemUp (item^.uid, itemNode item)
2016-03-15 15:35:35 +03:00
imgButton "move item down" "/arrow-thick-bottom.svg" [] $
2016-04-07 15:54:11 +03:00
JS.moveItemDown (item^.uid, itemNode item)
2016-03-15 15:35:35 +03:00
emptySpan "1.5em"
imgButton "edit item info" "/pencil.svg" [] $
JS.switchSection (this, "editing" :: Text)
emptySpan "0.5em"
imgButton "delete item" "/x.svg" [] $
2016-04-07 15:54:11 +03:00
JS.deleteItem (item^.uid, itemNode item)
2016-03-15 15:35:35 +03:00
-- TODO: link to Stackage too
-- TODO: should check for Stackage automatically
section "editing" [] $ do
let selectedIf p x = if p then with x [selected_ "selected"] else x
2016-03-17 03:35:56 +03:00
-- When the info/header node changes its group (and is hence
-- recolored), item's body has to be recolored too
let bodyNode = JS.selectChildren (JS.selectParent this)
(JS.selectClass "item-body")
2016-03-15 15:35:35 +03:00
let formSubmitHandler formNode =
2016-03-17 03:35:56 +03:00
JS.submitItemInfo (this, bodyNode, item^.uid, formNode)
2016-03-15 15:35:35 +03:00
form_ [onFormSubmit formSubmitHandler] $ do
-- All inputs have "autocomplete = off" thanks to
-- <http://stackoverflow.com/q/8311455>
label_ $ do
"Name" >> br_ []
input_ [type_ "text", name_ "name",
autocomplete_ "off",
value_ (item^.name)]
br_ []
label_ $ do
"Kind" >> br_ []
select_ [name_ "kind"] $ do
option_ [value_ "library"] "Library"
& selectedIf (case item^.kind of Library{} -> True; _ -> False)
option_ [value_ "tool"] "Tool"
& selectedIf (case item^.kind of Tool{} -> True; _ -> False)
option_ [value_ "other"] "Other"
& selectedIf (case item^.kind of Other{} -> True; _ -> False)
br_ []
label_ $ do
"Name on Hackage" >> br_ []
input_ [type_ "text", name_ "hackage-name", autocomplete_ "off",
value_ (fromMaybe "" (item^?kind.hackageName._Just))]
br_ []
label_ $ do
"Site (optional)" >> br_ []
input_ [type_ "text", name_ "link", autocomplete_ "off",
value_ (fromMaybe "" (item^.link))]
br_ []
2016-03-19 00:05:01 +03:00
newGroupInputId <- randomLongUid
2016-03-15 15:35:35 +03:00
label_ $ do
"Group" >> br_ []
-- When “new group” is selected in the list, we show a field for
-- entering new group's name
let selectHandler = [text|
if (this.value == "$newGroupValue") {
$("#$idText").show();
$("#$idText").focus(); }
else $("#$idText").hide(); |]
where idText = uidToText newGroupInputId
select_ [name_ "group", autocomplete_ "off",
onchange_ selectHandler] $ do
let gs = Nothing : map Just (M.keys (cat^.groups))
for_ gs $ \group' -> do
-- Text that will be shown in the list (“-” stands for “no
-- group”)
let txt = fromMaybe "-" group'
-- If the element corresponds to the current group of the
-- item (or the element is “-”, i.e. Nothing, and the group
-- is Nothing too), mark it as selected, thus making it the
-- element that will be chosen by default when the form is
-- rendered
option_ [value_ txt] (toHtml txt)
& selectedIf (group' == item^.group_)
option_ [value_ newGroupValue] "New group..."
input_ [uid_ newGroupInputId, type_ "text", autocomplete_ "off",
name_ "custom-group", hidden_ "hidden"]
br_ []
input_ [type_ "submit", value_ "Save"]
button "Cancel" [] $
JS.switchSection (this, "normal" :: Text)
-- TODO: categories that don't directly compare libraries but just list all
-- libraries about something (e.g. Yesod plugins, or whatever)
-- TODO: categories without items (e.g. “web dev”) that list links to other
-- categories
renderItemDescription :: MonadIO m => Item -> HtmlT m ()
2016-03-17 03:35:56 +03:00
renderItemDescription item = do
2016-03-15 15:35:35 +03:00
let thisId = "item-description-" <> uidToText (item^.uid)
this = JS.selectId thisId
2016-03-17 03:35:56 +03:00
div_ [id_ thisId, class_ "item-description"] $ do
2016-03-15 15:35:35 +03:00
section "normal" [shown, noScriptShown] $ do
if item^.description == ""
2016-03-15 15:35:35 +03:00
then p_ "write something here!"
else toHtml (item^.description)
2016-03-15 15:35:35 +03:00
textButton "edit description" $
JS.switchSection (this, "editing" :: Text)
section "editing" [] $
markdownEditor
[rows_ "10"]
2016-03-15 15:35:35 +03:00
(item^.description)
(\val -> JS.submitItemDescription (this, item^.uid, val))
(JS.switchSection (this, "normal" :: Text))
renderItemEcosystem :: MonadIO m => Item -> HtmlT m ()
2016-03-17 03:35:56 +03:00
renderItemEcosystem item = 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
strong_ "Ecosystem"
emptySpan "0.5em"
imgButton "edit ecosystem" "/pencil.svg"
[style_ "width:12px;opacity:0.5"] $
JS.switchSection (this, "editing" :: Text)
section "normal" [shown, noScriptShown] $ do
unless (item^.ecosystem == "") $
toHtml (item^.ecosystem)
2016-03-17 02:52:40 +03:00
section "editing" [] $
markdownEditor
2016-03-17 02:52:40 +03:00
[rows_ "3"]
(item^.ecosystem)
(\val -> JS.submitItemEcosystem (this, item^.uid, val))
(JS.switchSection (this, "normal" :: Text))
2016-03-17 02:52:40 +03:00
-- TODO: change MonadIO to MonadRandom mostly everywhere
renderItemTraits :: MonadIO m => Item -> HtmlT m ()
2016-03-17 03:35:56 +03:00
renderItemTraits item = do
div_ [class_ "item-traits"] $ do
2016-03-15 15:35:35 +03:00
this <- thisNode
div_ [class_ "traits-groups-container"] $ do
div_ [class_ "traits-group"] $ do
2016-03-17 03:02:51 +03:00
strong_ "Pros"
-- 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
ul_ [uid_ listUid] $
2016-03-15 15:35:35 +03:00
mapM_ (renderTrait (item^.uid)) (item^.pros)
section "editable" [] $
smallMarkdownEditor
[rows_ "3", placeholder_ "add pro"]
""
(\val -> JS.addPro (JS.selectUid listUid, item^.uid, val) <>
2016-03-15 15:35:35 +03:00
JS.assign val ("" :: Text))
Nothing
2016-03-17 03:02:51 +03:00
div_ (emptySpan "1em")
2016-03-15 15:35:35 +03:00
div_ [class_ "traits-group"] $ do
2016-03-17 03:02:51 +03:00
strong_ "Cons"
2016-03-15 15:35:35 +03:00
-- TODO: [easy] maybe add a line here?
2016-03-19 00:05:01 +03:00
listUid <- randomLongUid
ul_ [uid_ listUid] $
2016-03-15 15:35:35 +03:00
mapM_ (renderTrait (item^.uid)) (item^.cons)
section "editable" [] $
smallMarkdownEditor
[rows_ "3", placeholder_ "add con"]
""
(\val -> JS.addCon (JS.selectUid listUid, item^.uid, val) <>
2016-03-15 15:35:35 +03:00
JS.assign val ("" :: Text))
Nothing
section "normal" [shown, noScriptShown] $ do
textButton "edit pros/cons" $
2016-03-27 02:34:07 +03:00
-- Switches sections in *all* traits
2016-03-15 15:35:35 +03:00
JS.switchSectionsEverywhere(this, "editable" :: Text)
section "editable" [] $ do
textButton "edit off" $
JS.switchSectionsEverywhere(this, "normal" :: Text)
2016-04-09 11:13:26 +03:00
renderTrait :: MonadIO m => Uid Item -> Trait -> HtmlT m ()
2016-03-15 15:35:35 +03:00
renderTrait itemId trait = do
let thisId = "trait-" <> uidToText (trait^.uid)
this = JS.selectId thisId
editingSectionUid <- randomLongUid
2016-03-15 15:35:35 +03:00
li_ [id_ thisId] $ do
2016-04-11 23:31:30 +03:00
sectionSpan "normal editable" [shown, noScriptShown] $ do
toHtml (trait^.content)
2016-03-15 15:35:35 +03:00
2016-04-11 23:31:30 +03:00
sectionSpan "editable" [] $ do
2016-03-15 15:35:35 +03:00
br_ []
imgButton "move trait up" "/arrow-thick-top.svg" [width_ "12"] $
JS.moveTraitUp (itemId, trait^.uid, this)
imgButton "move trait down" "/arrow-thick-bottom.svg" [width_ "12"] $
JS.moveTraitDown (itemId, trait^.uid, this)
-- TODO: these 3 icons in a row don't look nice
imgButton "delete trait" "/x.svg" [width_ "12"] $
JS.deleteTrait (itemId, trait^.uid, this)
textareaUid <- randomLongUid
2016-03-15 15:35:35 +03:00
textButton "edit" $
JS.makeTraitEditor (this, JS.selectUid editingSectionUid,
textareaUid,
trait^.content.mdText,
itemId, trait^.uid) <>
JS.switchSection (this, "editing" :: Text) <>
JS.autosizeTextarea [JS.selectUid textareaUid]
2016-03-15 15:35:35 +03:00
section "editing" [uid_ editingSectionUid] $ do
return ()
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?)
-- TODO: [very-easy] focus the notes textarea on edit (can use jQuery's
-- .focus() on it)
renderItemNotes :: MonadIO m => Item -> HtmlT m ()
2016-03-17 03:35:56 +03:00
renderItemNotes item = do
-- 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
editingSectionUid <- randomLongUid
2016-03-17 03:35:56 +03:00
div_ [id_ thisId, class_ "item-notes"] $ do
2016-03-15 15:35:35 +03:00
section "collapsed" [shown] $ do
2016-04-16 02:02:43 +03:00
textButton "expand notes" $
JS.expandItemNotes [item^.uid]
2016-04-16 02:02:43 +03:00
br_ []
let toc = extractSections (item^.notes.mdMarkdown)
unless (null toc) $ div_ [class_ "notes-toc"] $ do
let renderTOC :: Monad m => Forest Inlines -> HtmlT m ()
renderTOC [] = return ()
renderTOC xs = ul_ $ do
for_ xs $ \(Node x children) -> li_ $ do
renderInlines def x
renderTOC children
renderTOC toc
2016-03-15 15:35:35 +03:00
section "expanded" [noScriptShown] $ do
textareaUid <- randomLongUid
contents <- if item^.notes == ""
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)
emptySpan "1em"
textButton "edit notes" $
JS.makeItemNotesEditor (
this, JS.selectUid editingSectionUid,
textareaUid,
contents,
item^.uid) <>
JS.switchSection (this, "editing" :: Text) <>
JS.autosizeTextarea [JS.selectUid textareaUid]
2016-03-15 15:35:35 +03:00
buttons
if item^.notes == ""
2016-03-15 15:35:35 +03:00
then p_ "add something!"
else toHtml (item^.notes) >>
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)
section "editing" [uid_ editingSectionUid] $
return ()
2016-03-15 15:35:35 +03:00
-- TODO: a shortcut for editing (when you press Ctrl-something, whatever was
-- selected becomes editable)
renderItemForFeed :: Monad m => Item -> HtmlT m ()
2016-03-19 21:36:21 +03:00
renderItemForFeed item = do
2016-03-21 02:12:03 +03:00
h1_ $ renderItemTitle item
2016-03-19 21:36:21 +03:00
when (item^.description /= "") $
toHtml (item^.description)
h2_ "Pros"
ul_ $ mapM_ (p_ . li_ . toHtml . view content) (item^.pros)
h2_ "Cons"
ul_ $ mapM_ (p_ . li_ . toHtml . view content) (item^.cons)
when (item^.ecosystem /= "") $ do
h2_ "Ecosystem"
toHtml (item^.ecosystem)
when (item^.notes /= "") $ do
h2_ "Notes"
toHtml (item^.notes)
2016-03-15 15:35:35 +03:00
-- Utils
onPageLoad :: Monad m => JS -> HtmlT m ()
2016-03-15 15:35:35 +03:00
onPageLoad js = script_ $ format "$(document).ready(function(){{}});" [js]
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_ $
format "if (event.keyCode == 13) {{} return false;}" [handler]
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
onFormSubmit f = onsubmit_ $ format "{} return false;" [f (JS "this")]
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
:: Monad m
=> Text -- ^ Button text
2016-03-15 15:35:35 +03:00
-> JS -- ^ Onclick handler
-> 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/>
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
markdownEditor
:: MonadIO m
=> [Attribute]
-> MarkdownBlock -- ^ Default text
-> (JS -> JS) -- ^ “Submit” handler, receiving the contents of the editor
-> JS -- ^ “Cancel” handler
-> HtmlT m ()
2016-04-16 02:02:43 +03:00
markdownEditor attr (view mdText -> s) submit cancel = do
2016-03-24 03:02:09 +03:00
textareaUid <- randomLongUid
2016-03-15 15:35:35 +03:00
-- Autocomplete has to be turned off thanks to
-- <http://stackoverflow.com/q/8311455>.
2016-03-24 03:02:09 +03:00
textarea_ ([uid_ textareaUid, autocomplete_ "off", class_ "big fullwidth"]
++ attr) $
2016-03-15 15:35:35 +03:00
toHtml s
2016-03-24 03:02:09 +03:00
let val = JS $ format "document.getElementById(\"{}\").value" [textareaUid]
2016-03-15 15:35:35 +03:00
button "Save" [] $
submit val
emptySpan "6px"
button "Cancel" [] $
JS.assign val s <>
cancel
emptySpan "6px"
"Markdown"
2016-03-24 03:02:09 +03:00
emptySpan "6px"
-- TODO: this jumps around when there's a lot of text, need to somehow
-- prevent jumping (and in JS.makeItemNotesEditor too)
2016-03-24 03:02:09 +03:00
let checkHandler = fromJS $
JS.setMonospace (JS.selectUid textareaUid, JS "this.checked")
label_ $ do
input_ [type_ "checkbox", name_ "monospace", onchange_ checkHandler]
"monospace editor"
2016-03-15 15:35:35 +03:00
smallMarkdownEditor
:: MonadIO m
=> [Attribute]
-> MarkdownInline -- ^ Default text
-> (JS -> JS) -- ^ “Submit” handler, receiving the contents of the editor
-> Maybe JS -- ^ “Cancel” handler (if “Cancel” is needed)
-> HtmlT m ()
2016-04-16 02:02:43 +03:00
smallMarkdownEditor attr (view mdText -> s) submit mbCancel = do
2016-03-19 00:05:01 +03:00
textareaId <- randomLongUid
2016-03-15 15:35:35 +03:00
let val = JS $ format "document.getElementById(\"{}\").value" [textareaId]
textarea_ ([class_ "fullwidth", uid_ textareaId, autocomplete_ "off",
onEnter (submit val)] ++ attr) $
2016-03-15 15:35:35 +03:00
toHtml s
case mbCancel of
Nothing -> return ()
Just cancel -> do
br_ []
textButton "cancel" $
JS.assign val s <>
cancel
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)
itemNode :: Item -> JQuerySelector
itemNode = JS.selectId . itemNodeId
categoryNodeId :: Category -> Text
categoryNodeId category = "category-" <> uidToText (category^.uid)
categoryNode :: Category -> JQuerySelector
categoryNode = JS.selectId . categoryNodeId
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)
newGroupValue :: Text
newGroupValue = "-new-group-"