File: Blaze.hs

package info (click to toggle)
haskell-blaze-html 0.4.3.1-3
  • links: PTS, VCS
  • area: main
  • in suites: wheezy
  • size: 720 kB
  • sloc: haskell: 7,924; makefile: 2
file content (179 lines) | stat: -rw-r--r-- 4,212 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
{-# LANGUAGE FlexibleInstances, TypeSynonymInstances #-}
-- | BlazeHtml is an HTML combinator library. It provides a way to embed HTML in
-- Haskell in an efficient and convenient way, with a light-weight syntax.
--
-- To use the library, one needs to import a set of HTML combinators. For
-- example, you can use HTML 4 Strict.
--
-- > {-# LANGUAGE OverloadedStrings #-}
-- > import Prelude hiding (head, id, div)
-- > import Text.Blaze.Html4.Strict hiding (map)
-- > import Text.Blaze.Html4.Strict.Attributes hiding (title)
--
-- To render the page later on, you need a so called Renderer. The recommended
-- renderer is an UTF-8 renderer which produces a lazy bytestring.
--
-- > import Text.Blaze.Renderer.Utf8 (renderHtml)
--
-- Now, you can describe pages using the imported combinators.
--
-- > page1 :: Html
-- > page1 = html $ do
-- >     head $ do
-- >         title "Introduction page."
-- >         link ! rel "stylesheet" ! type_ "text/css" ! href "screen.css"
-- >     body $ do
-- >         div ! id "header" $ "Syntax"
-- >         p "This is an example of BlazeHtml syntax."
-- >         ul $ mapM_ (li . toHtml . show) [1, 2, 3]
--
-- The resulting HTML can now be extracted using:
--
-- > renderHtml page1
--
module Text.Blaze
    (
      -- * Important types.
      Html
    , Tag
    , Attribute
    , AttributeValue

      -- * Creating attributes.
    , dataAttribute
    , customAttribute

      -- * Converting values to HTML.
    , ToHtml (..)
    , text
    , preEscapedText
    , lazyText
    , preEscapedLazyText
    , string
    , preEscapedString
    , unsafeByteString
    , unsafeLazyByteString

      -- * Creating tags.
    , textTag
    , stringTag

      -- * Converting values to attribute values.
    , ToValue (..)
    , textValue
    , preEscapedTextValue
    , lazyTextValue
    , preEscapedLazyTextValue
    , stringValue
    , preEscapedStringValue
    , unsafeByteStringValue
    , unsafeLazyByteStringValue

      -- * Setting attributes
    , (!)
    ) where

import Data.Monoid (mconcat)

import Data.Text (Text)
import qualified Data.Text.Lazy as LT

import Text.Blaze.Internal

-- | Class allowing us to use a single function for HTML values
--
class ToHtml a where
    -- | Convert a value to HTML.
    --
    toHtml :: a -> Html

instance ToHtml Html where
    toHtml = id
    {-# INLINE toHtml #-}

instance ToHtml [Html] where
    toHtml = mconcat
    {-# INLINE toHtml #-}

instance ToHtml Text where
    toHtml = text
    {-# INLINE toHtml #-}

instance ToHtml LT.Text where
    toHtml = lazyText
    {-# INLINE toHtml #-}

instance ToHtml String where
    toHtml = string
    {-# INLINE toHtml #-}

instance ToHtml Int where
    toHtml = string . show
    {-# INLINE toHtml #-}

instance ToHtml Char where
    toHtml = string . return
    {-# INLINE toHtml #-}

instance ToHtml Bool where
    toHtml = string . show
    {-# INLINE toHtml #-}

instance ToHtml Integer where
    toHtml = string . show
    {-# INLINE toHtml #-}

instance ToHtml Float where
    toHtml = string . show
    {-# INLINE toHtml #-}

instance ToHtml Double where
    toHtml = string . show
    {-# INLINE toHtml #-}

-- | Class allowing us to use a single function for attribute values
--
class ToValue a where
    -- | Convert a value to an HTML attribute value
    --
    toValue :: a -> AttributeValue

instance ToValue AttributeValue where
    toValue = id
    {-# INLINE toValue #-}

instance ToValue Text where
    toValue = textValue
    {-# INLINE toValue #-}

instance ToValue LT.Text where
    toValue = lazyTextValue
    {-# INLINE toValue #-}

instance ToValue String where
    toValue = stringValue
    {-# INLINE toValue #-}

instance ToValue Int where
    toValue = stringValue . show
    {-# INLINE toValue #-}

instance ToValue Char where
    toValue = stringValue . return
    {-# INLINE toValue #-}

instance ToValue Bool where
    toValue = stringValue . show
    {-# INLINE toValue #-}

instance ToValue Integer where
    toValue = stringValue . show
    {-# INLINE toValue #-}

instance ToValue Float where
    toValue = stringValue . show
    {-# INLINE toValue #-}

instance ToValue Double where
    toValue = stringValue . show
    {-# INLINE toValue #-}