Removed blaze-html
This commit is contained in:
parent
6b8eb05ae1
commit
02fd6bfffd
@ -16,10 +16,10 @@ codegen' s' = do
|
||||
let s = killFirstBlank s'
|
||||
case parse (many parseToken) s s of
|
||||
Left e -> error $ show e
|
||||
Right tokens -> do
|
||||
let tokens' = map toExp tokens
|
||||
Right tokens' -> do
|
||||
let tokens'' = map toExp tokens'
|
||||
concat' <- [|concat|]
|
||||
return $ concat' `AppE` ListE tokens'
|
||||
return $ concat' `AppE` ListE tokens''
|
||||
where
|
||||
killFirstBlank ('\n':x) = x
|
||||
killFirstBlank ('\r':'\n':x) = x
|
||||
|
||||
@ -18,7 +18,6 @@ module Yesod.Form
|
||||
, FormResult (..)
|
||||
, Enctype (..)
|
||||
, FieldInfo (..)
|
||||
, Html'
|
||||
-- * Unwrapping functions
|
||||
, runFormGet
|
||||
, runFormPost
|
||||
@ -157,12 +156,12 @@ mapFormXml f (GForm g) = GForm $ \e fe -> do
|
||||
-- write generic field functions and then different functions for producing
|
||||
-- actual HTML. See, for example, 'fieldsToTable' and 'fieldsToPlain'.
|
||||
data FieldInfo sub y = FieldInfo
|
||||
{ fiLabel :: Html ()
|
||||
, fiTooltip :: Html ()
|
||||
{ fiLabel :: Html
|
||||
, fiTooltip :: Html
|
||||
, fiIdent :: String
|
||||
, fiName :: String
|
||||
, fiInput :: GWidget sub y ()
|
||||
, fiErrors :: Maybe (Html ())
|
||||
, fiErrors :: Maybe Html
|
||||
}
|
||||
|
||||
type Env = [(String, String)]
|
||||
@ -211,8 +210,8 @@ class ToFormField a y where
|
||||
toFormField :: FormFieldSettings -> Maybe a -> FormField sub y a
|
||||
|
||||
data FormFieldSettings = FormFieldSettings
|
||||
{ ffsLabel :: Html ()
|
||||
, ffsTooltip :: Html ()
|
||||
{ ffsLabel :: Html
|
||||
, ffsTooltip :: Html
|
||||
, ffsId :: Maybe String
|
||||
, ffsName :: Maybe String
|
||||
}
|
||||
@ -467,13 +466,13 @@ boolField ffs orig = GForm $ \env _ -> do
|
||||
instance ToFormField Bool y where
|
||||
toFormField = boolField
|
||||
|
||||
htmlField :: FormFieldSettings -> FormletField sub y (Html ())
|
||||
htmlField :: FormFieldSettings -> FormletField sub y Html
|
||||
htmlField = requiredFieldHelper htmlFieldProfile
|
||||
|
||||
maybeHtmlField :: FormFieldSettings -> FormletField sub y (Maybe (Html ()))
|
||||
maybeHtmlField :: FormFieldSettings -> FormletField sub y (Maybe Html)
|
||||
maybeHtmlField = optionalFieldHelper htmlFieldProfile
|
||||
|
||||
htmlFieldProfile :: FieldProfile sub y (Html ())
|
||||
htmlFieldProfile :: FieldProfile sub y Html
|
||||
htmlFieldProfile = FieldProfile
|
||||
{ fpParse = Right . preEscapedString
|
||||
, fpRender = U.toString . renderHtml
|
||||
@ -482,13 +481,11 @@ htmlFieldProfile = FieldProfile
|
||||
|]
|
||||
, fpWidget = const $ return ()
|
||||
}
|
||||
instance ToFormField (Html ()) y where
|
||||
instance ToFormField Html y where
|
||||
toFormField = htmlField
|
||||
instance ToFormField (Maybe (Html ())) y where
|
||||
instance ToFormField (Maybe Html) y where
|
||||
toFormField = maybeHtmlField
|
||||
|
||||
type Html' = Html ()
|
||||
|
||||
readMay :: Read a => String -> Maybe a
|
||||
readMay s = case reads s of
|
||||
(x, _):_ -> Just x
|
||||
|
||||
@ -16,13 +16,13 @@ class YesodNic a where
|
||||
urlNicEdit :: a -> Either (Route a) String
|
||||
urlNicEdit _ = Right "http://js.nicedit.com/nicEdit-latest.js"
|
||||
|
||||
nicHtmlField :: YesodNic y => FormFieldSettings -> FormletField sub y (Html ())
|
||||
nicHtmlField :: YesodNic y => FormFieldSettings -> FormletField sub y Html
|
||||
nicHtmlField = requiredFieldHelper nicHtmlFieldProfile
|
||||
|
||||
maybeNicHtmlField :: YesodNic y => FormFieldSettings -> FormletField sub y (Maybe (Html ()))
|
||||
maybeNicHtmlField :: YesodNic y => FormFieldSettings -> FormletField sub y (Maybe Html)
|
||||
maybeNicHtmlField = optionalFieldHelper nicHtmlFieldProfile
|
||||
|
||||
nicHtmlFieldProfile :: YesodNic y => FieldProfile sub y (Html ())
|
||||
nicHtmlFieldProfile :: YesodNic y => FieldProfile sub y Html
|
||||
nicHtmlFieldProfile = FieldProfile
|
||||
{ fpParse = Right . preEscapedString
|
||||
, fpRender = U.toString . renderHtml
|
||||
|
||||
@ -42,7 +42,7 @@ import Yesod.Handler
|
||||
--
|
||||
-- > PageContent url -> Hamlet url
|
||||
data PageContent url = PageContent
|
||||
{ pageTitle :: Html ()
|
||||
{ pageTitle :: Html
|
||||
, pageHead :: Hamlet url
|
||||
, pageBody :: Hamlet url
|
||||
}
|
||||
|
||||
@ -332,14 +332,14 @@ msgKey = "_MSG"
|
||||
-- instead, it will only appear in the next request.
|
||||
--
|
||||
-- See 'getMessage'.
|
||||
setMessage :: Html () -> GHandler sub master ()
|
||||
setMessage :: Html -> GHandler sub master ()
|
||||
setMessage = setSession msgKey . L.toString . renderHtml
|
||||
|
||||
-- | Gets the message in the user's session, if available, and then clears the
|
||||
-- variable.
|
||||
--
|
||||
-- See 'setMessage'.
|
||||
getMessage :: GHandler sub master (Maybe (Html ()))
|
||||
getMessage :: GHandler sub master (Maybe Html)
|
||||
getMessage = do
|
||||
deleteSession msgKey
|
||||
fmap (fmap preEscapedString) $ lookupSession msgKey
|
||||
|
||||
@ -44,7 +44,7 @@ data AtomFeedEntry url = AtomFeedEntry
|
||||
{ atomEntryLink :: url
|
||||
, atomEntryUpdated :: UTCTime
|
||||
, atomEntryTitle :: String
|
||||
, atomEntryContent :: Html ()
|
||||
, atomEntryContent :: Html
|
||||
}
|
||||
|
||||
template :: AtomFeed url -> Hamlet url
|
||||
|
||||
@ -25,7 +25,7 @@ import Yesod.Handler
|
||||
import Numeric (showHex)
|
||||
import Data.Monoid (Monoid (..))
|
||||
import Text.Blaze.Builder.Core
|
||||
import Text.Blaze (Html, renderHtml, string)
|
||||
import Text.Hamlet (Html, renderHtml, string)
|
||||
|
||||
#if TEST
|
||||
import Test.Framework (testGroup, Test)
|
||||
@ -63,7 +63,7 @@ jsonToRepJson = fmap RepJson . jsonToContent
|
||||
-- * Performs JSON encoding.
|
||||
--
|
||||
-- * Wraps the resulting string in quotes.
|
||||
jsonScalar :: Html () -> Json
|
||||
jsonScalar :: Html -> Json
|
||||
jsonScalar s = Json $ mconcat
|
||||
[ fromByteString "\""
|
||||
-- FIXME the following line can be optimized after blaze-html 0.2
|
||||
|
||||
@ -47,7 +47,7 @@ import Control.Monad.Trans.Class (lift)
|
||||
import "MonadCatchIO-transformers" Control.Monad.CatchIO (MonadCatchIO)
|
||||
import qualified Data.ByteString.Lazy as L
|
||||
import qualified Data.ByteString as S
|
||||
import Text.Blaze (unsafeByteString)
|
||||
import Text.Hamlet (unsafeByteString)
|
||||
|
||||
data Location url = Local url | Remote String
|
||||
deriving (Show, Eq)
|
||||
@ -68,7 +68,7 @@ newtype Script url = Script { unScript :: Location url }
|
||||
deriving (Show, Eq)
|
||||
newtype Stylesheet url = Stylesheet { unStylesheet :: Location url }
|
||||
deriving (Show, Eq)
|
||||
newtype Title = Title { unTitle :: Html () }
|
||||
newtype Title = Title { unTitle :: Html }
|
||||
newtype Head url = Head (Hamlet url)
|
||||
deriving Monoid
|
||||
newtype Body url = Body (Hamlet url)
|
||||
@ -102,7 +102,7 @@ liftHandler = GWidget . lift . lift . lift . lift . lift . lift . lift . lift
|
||||
|
||||
-- | Set the page title. Calling 'setTitle' multiple times overrides previously
|
||||
-- set values.
|
||||
setTitle :: Html () -> GWidget sub master ()
|
||||
setTitle :: Html -> GWidget sub master ()
|
||||
setTitle = GWidget . lift . tell . Last . Just . Title
|
||||
|
||||
-- | Add some raw HTML to the head tag.
|
||||
|
||||
@ -33,7 +33,6 @@ library
|
||||
web-routes >= 0.23 && < 0.24,
|
||||
web-routes-quasi >= 0.6 && < 0.7,
|
||||
hamlet >= 0.5.0 && < 0.6,
|
||||
blaze-html >= 0.1.1 && < 0.2,
|
||||
blaze-builder >= 0.1 && < 0.2,
|
||||
transformers >= 0.2 && < 0.3,
|
||||
clientsession >= 0.4.0 && < 0.5,
|
||||
|
||||
Loading…
Reference in New Issue
Block a user