{-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE CPP #-} {-# LANGUAGE OverloadedStrings #-} -- | Provide the user with a rich text editor. module Yesod.Form.Nic ( YesodNic (..) , nicHtmlField , maybeNicHtmlField ) where import Yesod.Handler import Yesod.Form.Core import Yesod.Widget import Text.HTML.SanitizeXSS (sanitizeBalance) import Text.Hamlet (Html, hamlet) import Text.Julius (julius) import Text.Blaze.Renderer.String (renderHtml) import Text.Blaze (preEscapedString) import Control.Monad.Trans.Class (lift) import Data.Text (Text, pack, unpack) class YesodNic a where -- | NIC Editor Javascript file. urlNicEdit :: a -> Either (Route a) Text urlNicEdit _ = Right "http://js.nicedit.com/nicEdit-latest.js" nicHtmlField :: (IsForm f, FormType f ~ Html, YesodNic (FormMaster f)) => FormFieldSettings -> Maybe Html -> f nicHtmlField = requiredFieldHelper nicHtmlFieldProfile maybeNicHtmlField :: (IsForm f, FormType f ~ Maybe Html, YesodNic (FormMaster f)) => FormFieldSettings -> Maybe (FormType f) -> f maybeNicHtmlField = optionalFieldHelper nicHtmlFieldProfile nicHtmlFieldProfile :: YesodNic y => FieldProfile sub y Html nicHtmlFieldProfile = FieldProfile { fpParse = Right . preEscapedString . sanitizeBalance . unpack -- FIXME , fpRender = pack . renderHtml , fpWidget = \theId name val _isReq -> do addHtml #if __GLASGOW_HASKELL__ >= 700 [hamlet| #else [$hamlet| #endif