{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeSynonymInstances #-}
module Text.Blaze
(
Markup
, Tag
, Attribute
, AttributeValue
, dataAttribute
, customAttribute
, ToMarkup (..)
, text
, preEscapedText
, lazyText
, preEscapedLazyText
, string
, preEscapedString
, unsafeByteString
, unsafeLazyByteString
, textComment
, lazyTextComment
, stringComment
, unsafeByteStringComment
, unsafeLazyByteStringComment
, textTag
, stringTag
, ToValue (..)
, textValue
, preEscapedTextValue
, lazyTextValue
, preEscapedLazyTextValue
, stringValue
, preEscapedStringValue
, unsafeByteStringValue
, unsafeLazyByteStringValue
, (!)
, (!?)
, contents
) where
import Data.Int (Int32, Int64)
import Data.Monoid (mconcat)
import Data.Word (Word, Word32, Word64)
#if MIN_VERSION_base(4,8,0)
import Numeric.Natural (Natural)
#endif
#if MIN_VERSION_base(4,9,0)
import Data.List.NonEmpty (NonEmpty (..))
#endif
import Data.Text (Text)
import qualified Data.Text.Lazy as LT
import qualified Data.Text.Lazy.Builder as LTB
import Text.Blaze.Internal
class ToMarkup a where
toMarkup :: a -> Markup
preEscapedToMarkup :: a -> Markup
preEscapedToMarkup = forall a. ToMarkup a => a -> Markup
toMarkup
{-# INLINE preEscapedToMarkup #-}
instance ToMarkup Markup where
toMarkup :: Markup -> Markup
toMarkup = forall a. a -> a
id
{-# INLINE toMarkup #-}
instance ToMarkup [Markup] where
toMarkup :: [Markup] -> Markup
toMarkup = forall a. Monoid a => [a] -> a
mconcat
{-# INLINE toMarkup #-}
instance ToMarkup Text where
toMarkup :: Text -> Markup
toMarkup = Text -> Markup
text
{-# INLINE toMarkup #-}
preEscapedToMarkup :: Text -> Markup
preEscapedToMarkup = Text -> Markup
preEscapedText
{-# INLINE preEscapedToMarkup #-}
instance ToMarkup LT.Text where
toMarkup :: Text -> Markup
toMarkup = Text -> Markup
lazyText
{-# INLINE toMarkup #-}
preEscapedToMarkup :: Text -> Markup
preEscapedToMarkup = Text -> Markup
preEscapedLazyText
{-# INLINE preEscapedToMarkup #-}
instance ToMarkup LTB.Builder where
toMarkup :: Builder -> Markup
toMarkup = Builder -> Markup
textBuilder
{-# INLINE toMarkup #-}
preEscapedToMarkup :: Builder -> Markup
preEscapedToMarkup = Builder -> Markup
preEscapedTextBuilder
{-# INLINE preEscapedToMarkup #-}
instance ToMarkup String where
toMarkup :: String -> Markup
toMarkup = String -> Markup
string
{-# INLINE toMarkup #-}
preEscapedToMarkup :: String -> Markup
preEscapedToMarkup = String -> Markup
preEscapedString
{-# INLINE preEscapedToMarkup #-}
instance ToMarkup Int where
toMarkup :: Int -> Markup
toMarkup = String -> Markup
string forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
{-# INLINE toMarkup #-}
instance ToMarkup Int32 where
toMarkup :: Int32 -> Markup
toMarkup = String -> Markup
string forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
{-# INLINE toMarkup #-}
instance ToMarkup Int64 where
toMarkup :: Int64 -> Markup
toMarkup = String -> Markup
string forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
{-# INLINE toMarkup #-}
#if MIN_VERSION_base(4,8,0)
instance ToMarkup Natural where
toMarkup :: Natural -> Markup
toMarkup = String -> Markup
string forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
{-# INLINE toMarkup #-}
#endif
instance ToMarkup Char where
toMarkup :: Char -> Markup
toMarkup = String -> Markup
string forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. Monad m => a -> m a
return
{-# INLINE toMarkup #-}
instance ToMarkup Bool where
toMarkup :: Bool -> Markup
toMarkup = String -> Markup
string forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
{-# INLINE toMarkup #-}
instance ToMarkup Integer where
toMarkup :: Integer -> Markup
toMarkup = String -> Markup
string forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
{-# INLINE toMarkup #-}
instance ToMarkup Float where
toMarkup :: Float -> Markup
toMarkup = String -> Markup
string forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
{-# INLINE toMarkup #-}
instance ToMarkup Double where
toMarkup :: Double -> Markup
toMarkup = String -> Markup
string forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
{-# INLINE toMarkup #-}
instance ToMarkup Word where
toMarkup :: Word -> Markup
toMarkup = String -> Markup
string forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
{-# INLINE toMarkup #-}
instance ToMarkup Word32 where
toMarkup :: Word32 -> Markup
toMarkup = String -> Markup
string forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
{-# INLINE toMarkup #-}
instance ToMarkup Word64 where
toMarkup :: Word64 -> Markup
toMarkup = String -> Markup
string forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
{-# INLINE toMarkup #-}
class ToValue a where
toValue :: a -> AttributeValue
preEscapedToValue :: a -> AttributeValue
preEscapedToValue = forall a. ToValue a => a -> AttributeValue
toValue
{-# INLINE preEscapedToValue #-}
instance ToValue AttributeValue where
toValue :: AttributeValue -> AttributeValue
toValue = forall a. a -> a
id
{-# INLINE toValue #-}
instance ToValue Text where
toValue :: Text -> AttributeValue
toValue = Text -> AttributeValue
textValue
{-# INLINE toValue #-}
preEscapedToValue :: Text -> AttributeValue
preEscapedToValue = Text -> AttributeValue
preEscapedTextValue
{-# INLINE preEscapedToValue #-}
instance ToValue LT.Text where
toValue :: Text -> AttributeValue
toValue = Text -> AttributeValue
lazyTextValue
{-# INLINE toValue #-}
preEscapedToValue :: Text -> AttributeValue
preEscapedToValue = Text -> AttributeValue
preEscapedLazyTextValue
{-# INLINE preEscapedToValue #-}
instance ToValue LTB.Builder where
toValue :: Builder -> AttributeValue
toValue = Builder -> AttributeValue
textBuilderValue
{-# INLINE toValue #-}
preEscapedToValue :: Builder -> AttributeValue
preEscapedToValue = Builder -> AttributeValue
preEscapedTextBuilderValue
{-# INLINE preEscapedToValue #-}
instance ToValue String where
toValue :: String -> AttributeValue
toValue = String -> AttributeValue
stringValue
{-# INLINE toValue #-}
preEscapedToValue :: String -> AttributeValue
preEscapedToValue = String -> AttributeValue
preEscapedStringValue
{-# INLINE preEscapedToValue #-}
instance ToValue Int where
toValue :: Int -> AttributeValue
toValue = String -> AttributeValue
stringValue forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
{-# INLINE toValue #-}
instance ToValue Int32 where
toValue :: Int32 -> AttributeValue
toValue = String -> AttributeValue
stringValue forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
{-# INLINE toValue #-}
instance ToValue Int64 where
toValue :: Int64 -> AttributeValue
toValue = String -> AttributeValue
stringValue forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
{-# INLINE toValue #-}
instance ToValue Char where
toValue :: Char -> AttributeValue
toValue = String -> AttributeValue
stringValue forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. Monad m => a -> m a
return
{-# INLINE toValue #-}
instance ToValue Bool where
toValue :: Bool -> AttributeValue
toValue = String -> AttributeValue
stringValue forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
{-# INLINE toValue #-}
instance ToValue Integer where
toValue :: Integer -> AttributeValue
toValue = String -> AttributeValue
stringValue forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
{-# INLINE toValue #-}
instance ToValue Float where
toValue :: Float -> AttributeValue
toValue = String -> AttributeValue
stringValue forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
{-# INLINE toValue #-}
instance ToValue Double where
toValue :: Double -> AttributeValue
toValue = String -> AttributeValue
stringValue forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
{-# INLINE toValue #-}
instance ToValue Word where
toValue :: Word -> AttributeValue
toValue = String -> AttributeValue
stringValue forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
{-# INLINE toValue #-}
instance ToValue Word32 where
toValue :: Word32 -> AttributeValue
toValue = String -> AttributeValue
stringValue forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
{-# INLINE toValue #-}
instance ToValue Word64 where
toValue :: Word64 -> AttributeValue
toValue = String -> AttributeValue
stringValue forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
{-# INLINE toValue #-}
#if MIN_VERSION_base(4,9,0)
instance ToMarkup (NonEmpty Char) where
toMarkup :: NonEmpty Char -> Markup
toMarkup (Char
x :| String
xs) = String -> Markup
string (Char
x forall a. a -> [a] -> [a]
: String
xs)
preEscapedToMarkup :: NonEmpty Char -> Markup
preEscapedToMarkup (Char
x :| String
xs) = String -> Markup
preEscapedString (Char
x forall a. a -> [a] -> [a]
: String
xs)
instance ToValue (NonEmpty Char) where
toValue :: NonEmpty Char -> AttributeValue
toValue (Char
x :| String
xs) = String -> AttributeValue
stringValue (Char
x forall a. a -> [a] -> [a]
: String
xs)
#endif