{-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE CPP #-} -- | Provide the user with a rich text editor. -- -- According to NIC editor homepage it is not actively maintained since June -- 2012. There is another better alternative — open sourced Summernote editor -- released under MIT licence. You can use Summernote in your Yesod forms via -- separately distributed -- -- package. module Yesod.Form.Nic ( YesodNic (..) , nicHtmlField ) where import Yesod.Core import Yesod.Form import Text.HTML.SanitizeXSS (sanitizeBalance) import Text.Julius (rawJS) import Text.Blaze.Html.Renderer.String (renderHtml) import Data.Text (Text, pack) import Data.Maybe (listToMaybe) class Yesod a => YesodNic a where -- | NIC Editor Javascript file. urlNicEdit :: a -> Either (Route a) Text urlNicEdit _ = Right "http://js.nicedit.com/nicEdit-latest.js" nicHtmlField :: YesodNic site => Field (HandlerFor site) Html nicHtmlField = Field { fieldParse = \e _ -> return . Right . fmap (preEscapedToMarkup . sanitizeBalance) . listToMaybe $ e , fieldView = \theId name attrs val _isReq -> do toWidget [shamlet| $newline never