| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Text.Html.Nice.FreeMonad
Contents
Description
A Free monad-based HTML markup monad. Unlike the writer-like monad in
Text.Html.Nice.Writer, sequencing bits of markup together results in them
being nested, rather than concatenated.
There is no kitchen-sink of HTML5 elements provided. Use OverloadedLabels
instead: #div :: Markup n () and #div :: MakeNode n () .
Since the monad and applicative of Markup here nests rather than
concatenates, the function nodes is provided to put a list of nodes
in sequence. You can use OverloadedLists for convenient syntax here.
Example Markup:
#html >> [ title >> "Title goes here" , #body >> [ #h1 >> "heading goes here" , #p >> "i am a paragraph below the heading" , do i <- branch [0..100] builder (decimal i) ] ]
- data Markup n a
- data FastMarkup a
- runMarkup :: Markup n a -> Markup' n
- compile :: Markup n a -> FastMarkup n
- renderM :: Monad m => (a -> m Builder) -> FastMarkup a -> m Builder
- renderMs :: Monad m => (a -> m (FastMarkup Void)) -> FastMarkup a -> m Builder
- render :: FastMarkup Void -> Builder
- newtype Identity a :: * -> * = Identity {
- runIdentity :: a
- toLazyText :: Builder -> Text
- doctype :: Markup n a
- node :: Text -> [Attr n] -> Markup n ()
- data Attr a
- attr :: MakeNode n a -> [Attr n] -> Markup n a
- empty :: Markup n a
- text :: Text -> Markup n a
- lazyText :: Text -> Markup n a
- builder :: Builder -> Markup n a
- unescape :: Text -> Markup n a
- string :: String -> Markup n a
- dynamic :: n -> Markup n a
- hole :: Markup (a -> a) t
- embed :: (t -> FastMarkup n) -> Markup (t -> FastMarkup n) a
- nodes :: [Markup n a] -> Markup n a
- branch :: [a] -> Markup n a
- stream :: Foldable f => Markup (a -> n) r' -> Markup (f a -> FastMarkup n) r
- sub :: Markup n a -> Markup (FastMarkup n) a
- decimal :: Integral a => a -> Builder
- realFloat :: RealFloat a => a -> Builder
- fromText :: Text -> Builder
- fromString :: String -> Builder
- fromLazyText :: Text -> Builder
- data Builder :: *
- data Void :: *
Markup
Markup is a free monad based on the base functor to 'Markup\'F'
Beware: this is a wacky monad. >> does *not* sequence nodes together;
instead, it nests them. To lay out nodes sequentially, use nodes.
Syntactic sugar
Markup supports OverloadedLabels, OverloadedStrings and
OverloadedLists.
OverloadedStrings
("foo" :: Markup n a) = text "foo"OverloadedLists
([a,b,c] :: Markup n a) = nodes [a,b,c]OverloadedLabels
The IsLabel instances give a convenient way to write nodes.
Nodes without attributes
(#foo ::Markupn a) =node"foo" []
Nodes with attributes
attr#foo [a,b,c] =node"foo" [a,b,c]
Instances
| Bifunctor Markup Source # | |
| ((~) * a (), KnownSymbol s) => IsLabel s (Markup n a) Source # | |
| Monad (Markup n) Source # | |
| Functor (Markup n) Source # | |
| Applicative (Markup n) Source # | |
| MonadFree (Markup'F n) (Markup n) Source # | |
| IsList (Markup n a) Source # | |
| IsString (Markup n a) Source # | |
| Monoid (Markup n a) Source # | |
| Default (Markup n a) Source # | |
| type Item (Markup n a) Source # | |
data FastMarkup a Source #
Instances
| Functor FastMarkup Source # | |
| Foldable FastMarkup Source # | |
| Eq a => Eq (FastMarkup a) Source # | |
| Show a => Show (FastMarkup a) Source # | |
| Generic (FastMarkup a) Source # | |
| Monoid (FastMarkup a) Source # | |
| NFData a => NFData (FastMarkup a) Source # | |
| ToFastMarkup (FastMarkup Void) Source # | |
| (Render a m, Monad m) => Render (FastMarkup a) m Source # | |
| type Rep (FastMarkup a) Source # | |
Compiling
compile :: Markup n a -> FastMarkup n Source #
Rendering
Rendering through some monad
renderM :: Monad m => (a -> m Builder) -> FastMarkup a -> m Builder Source #
Render FastMarkup
renderMs :: Monad m => (a -> m (FastMarkup Void)) -> FastMarkup a -> m Builder Source #
Render FastMarkup by recursively rendering any sub-markup.
Pure rendering
render :: FastMarkup Void -> Builder Source #
Render FastMarkup that has no holes.
newtype Identity a :: * -> * #
Identity functor and monad. (a non-strict monad)
Since: 4.8.0.0
Constructors
| Identity | |
Fields
| |
Instances
Util
toLazyText :: Builder -> Text #
O(n). Extract a lazy Text from a Builder with a default
buffer size. The construction work takes place if and when the
relevant part of the lazy Text is demanded.
Special HTML elements
Basic node types
Constructors
| (:=) | |
| (:-) | |
Fields
| |
Text types
Dynamic nodes
embed :: (t -> FastMarkup n) -> Markup (t -> FastMarkup n) a Source #
Insert a sub-template.
Sequential nodes
branch :: [a] -> Markup n a Source #
For each element of a list of branches, generate sequential markup
Streamed dynamic nodes
Combinators
Useful exports
Useful Builder functions
realFloat :: RealFloat a => a -> Builder #
Show a signed RealFloat value to full precision,
using standard decimal notation for arguments whose absolute value lies
between 0.1 and 9,999,999, and scientific notation otherwise.
O(1). A Builder taking a Text, satisfying
toLazyText(fromTextt) =fromChunks[t]
fromString :: String -> Builder #
O(1). A Builder taking a String, satisfying
toLazyText(fromStrings) =fromChunks[S.pack s]
fromLazyText :: Text -> Builder #
O(1). A Builder taking a lazy Text, satisfying
toLazyText(fromLazyTextt) = t
Text builder
A Builder is an efficient way to build lazy Text values.
There are several functions for constructing builders, but only one
to inspect them: to extract any data, you have to turn them into
lazy Text values using toLazyText.
Internally, a builder constructs a lazy Text by filling arrays
piece by piece. As each buffer is filled, it is 'popped' off, to
become a new chunk of the resulting lazy Text. All this is
hidden from the user of the Builder.
Void type
Uninhabited data type
Since: 4.8.0.0
Instances
| Eq Void | Since: 4.8.0.0 |
| Data Void | |
| Ord Void | Since: 4.8.0.0 |
| Read Void | Reading a |
| Show Void | Since: 4.8.0.0 |
| Ix Void | Since: 4.8.0.0 |
| Generic Void | |
| Semigroup Void | Since: 4.9.0.0 |
| Exception Void | Since: 4.8.0.0 |
| NFData Void | Since: 1.4.0.0 |
| Monad m => Render Void m Source # | |
| ToFastMarkup (FastMarkup Void) Source # | |
| type Rep Void | |