{-# 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
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 = toMarkup
{-# INLINE preEscapedToMarkup #-}
instance ToMarkup Markup where
toMarkup = id
{-# INLINE toMarkup #-}
instance ToMarkup [Markup] where
toMarkup = mconcat
{-# INLINE toMarkup #-}
instance ToMarkup Text where
toMarkup = text
{-# INLINE toMarkup #-}
preEscapedToMarkup = preEscapedText
{-# INLINE preEscapedToMarkup #-}
instance ToMarkup LT.Text where
toMarkup = lazyText
{-# INLINE toMarkup #-}
preEscapedToMarkup = preEscapedLazyText
{-# INLINE preEscapedToMarkup #-}
instance ToMarkup LTB.Builder where
toMarkup = textBuilder
{-# INLINE toMarkup #-}
preEscapedToMarkup = preEscapedTextBuilder
{-# INLINE preEscapedToMarkup #-}
instance ToMarkup String where
toMarkup = string
{-# INLINE toMarkup #-}
preEscapedToMarkup = preEscapedString
{-# INLINE preEscapedToMarkup #-}
instance ToMarkup Int where
toMarkup = string . show
{-# INLINE toMarkup #-}
instance ToMarkup Int32 where
toMarkup = string . show
{-# INLINE toMarkup #-}
instance ToMarkup Int64 where
toMarkup = string . show
{-# INLINE toMarkup #-}
#if MIN_VERSION_base(4,8,0)
instance ToMarkup Natural where
toMarkup = string . show
{-# INLINE toMarkup #-}
#endif
instance ToMarkup Char where
toMarkup = string . return
{-# INLINE toMarkup #-}
instance ToMarkup Bool where
toMarkup = string . show
{-# INLINE toMarkup #-}
instance ToMarkup Integer where
toMarkup = string . show
{-# INLINE toMarkup #-}
instance ToMarkup Float where
toMarkup = string . show
{-# INLINE toMarkup #-}
instance ToMarkup Double where
toMarkup = string . show
{-# INLINE toMarkup #-}
instance ToMarkup Word where
toMarkup = string . show
{-# INLINE toMarkup #-}
instance ToMarkup Word32 where
toMarkup = string . show
{-# INLINE toMarkup #-}
instance ToMarkup Word64 where
toMarkup = string . show
{-# INLINE toMarkup #-}
class ToValue a where
toValue :: a -> AttributeValue
preEscapedToValue :: a -> AttributeValue
preEscapedToValue = toValue
{-# INLINE preEscapedToValue #-}
instance ToValue AttributeValue where
toValue = id
{-# INLINE toValue #-}
instance ToValue Text where
toValue = textValue
{-# INLINE toValue #-}
preEscapedToValue = preEscapedTextValue
{-# INLINE preEscapedToValue #-}
instance ToValue LT.Text where
toValue = lazyTextValue
{-# INLINE toValue #-}
preEscapedToValue = preEscapedLazyTextValue
{-# INLINE preEscapedToValue #-}
instance ToValue LTB.Builder where
toValue = textBuilderValue
{-# INLINE toValue #-}
preEscapedToValue = preEscapedTextBuilderValue
{-# INLINE preEscapedToValue #-}
instance ToValue String where
toValue = stringValue
{-# INLINE toValue #-}
preEscapedToValue = preEscapedStringValue
{-# INLINE preEscapedToValue #-}
instance ToValue Int where
toValue = stringValue . show
{-# INLINE toValue #-}
instance ToValue Int32 where
toValue = stringValue . show
{-# INLINE toValue #-}
instance ToValue Int64 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 #-}
instance ToValue Word where
toValue = stringValue . show
{-# INLINE toValue #-}
instance ToValue Word32 where
toValue = stringValue . show
{-# INLINE toValue #-}
instance ToValue Word64 where
toValue = stringValue . show
{-# INLINE toValue #-}