{-# LANGUAGE CPP                  #-}
{-# LANGUAGE FlexibleInstances    #-}
{-# LANGUAGE OverloadedStrings    #-}
{-# LANGUAGE TypeSynonymInstances #-}
-- | BlazeMarkup is a markup combinator library. It provides a way to embed
-- markup languages like HTML and SVG in Haskell in an efficient and convenient
-- way, with a light-weight syntax.
--
-- To use the library, one needs to import a set of combinators. For example,
-- you can use HTML 4 Strict from BlazeHtml package.
--
-- > {-# 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 (renderMarkup)
--
-- Now, you can describe pages using the imported combinators.
--
-- > page1 :: Markup
-- > 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 BlazeMarkup syntax."
-- >         ul $ mapM_ (li . toMarkup . show) [1, 2, 3]
--
-- The resulting HTML can now be extracted using:
--
-- > renderMarkup page1
--
module Text.Blaze
    (
      -- * Important types.
      Markup
    , Tag
    , Attribute
    , AttributeValue

      -- * Creating attributes.
    , dataAttribute
    , customAttribute

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

      -- * Comments
    , textComment
    , lazyTextComment
    , stringComment
    , unsafeByteStringComment
    , unsafeLazyByteStringComment

      -- * Creating tags.
    , textTag
    , stringTag

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

      -- * Setting attributes
    , (!)
    , (!?)

      -- * Modifiying Markup trees
    , 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 allowing us to use a single function for Markup values
--
class ToMarkup a where
    -- | Convert a value to Markup.
    --
    toMarkup :: a -> Markup

    -- | Convert a value to Markup without escaping
    --
    preEscapedToMarkup :: a -> Markup
    preEscapedToMarkup = a -> Markup
forall a. ToMarkup a => a -> Markup
toMarkup
    {-# INLINE preEscapedToMarkup #-}

instance ToMarkup Markup where
    toMarkup :: Markup -> Markup
toMarkup = Markup -> Markup
forall a. a -> a
id
    {-# INLINE toMarkup #-}

instance ToMarkup [Markup] where
    toMarkup :: [Markup] -> Markup
toMarkup = [Markup] -> Markup
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 (String -> Markup) -> (Int -> String) -> Int -> Markup
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String
forall a. Show a => a -> String
show
    {-# INLINE toMarkup #-}

instance ToMarkup Int32 where
    toMarkup :: Int32 -> Markup
toMarkup = String -> Markup
string (String -> Markup) -> (Int32 -> String) -> Int32 -> Markup
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int32 -> String
forall a. Show a => a -> String
show
    {-# INLINE toMarkup #-}

instance ToMarkup Int64 where
    toMarkup :: Int64 -> Markup
toMarkup = String -> Markup
string (String -> Markup) -> (Int64 -> String) -> Int64 -> Markup
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> String
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 (String -> Markup) -> (Natural -> String) -> Natural -> Markup
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Natural -> String
forall a. Show a => a -> String
show
    {-# INLINE toMarkup #-}
#endif

instance ToMarkup Char where
    toMarkup :: Char -> Markup
toMarkup = String -> Markup
string (String -> Markup) -> (Char -> String) -> Char -> Markup
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> String
forall (m :: * -> *) a. Monad m => a -> m a
return
    {-# INLINE toMarkup #-}

instance ToMarkup Bool where
    toMarkup :: Bool -> Markup
toMarkup = String -> Markup
string (String -> Markup) -> (Bool -> String) -> Bool -> Markup
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> String
forall a. Show a => a -> String
show
    {-# INLINE toMarkup #-}

instance ToMarkup Integer where
    toMarkup :: Integer -> Markup
toMarkup = String -> Markup
string (String -> Markup) -> (Integer -> String) -> Integer -> Markup
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> String
forall a. Show a => a -> String
show
    {-# INLINE toMarkup #-}

instance ToMarkup Float where
    toMarkup :: Float -> Markup
toMarkup = String -> Markup
string (String -> Markup) -> (Float -> String) -> Float -> Markup
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Float -> String
forall a. Show a => a -> String
show
    {-# INLINE toMarkup #-}

instance ToMarkup Double where
    toMarkup :: Double -> Markup
toMarkup = String -> Markup
string (String -> Markup) -> (Double -> String) -> Double -> Markup
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> String
forall a. Show a => a -> String
show
    {-# INLINE toMarkup #-}

instance ToMarkup Word where
    toMarkup :: Word -> Markup
toMarkup = String -> Markup
string (String -> Markup) -> (Word -> String) -> Word -> Markup
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word -> String
forall a. Show a => a -> String
show
    {-# INLINE toMarkup #-}

instance ToMarkup Word32 where
    toMarkup :: Word32 -> Markup
toMarkup = String -> Markup
string (String -> Markup) -> (Word32 -> String) -> Word32 -> Markup
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> String
forall a. Show a => a -> String
show
    {-# INLINE toMarkup #-}

instance ToMarkup Word64 where
    toMarkup :: Word64 -> Markup
toMarkup = String -> Markup
string (String -> Markup) -> (Word64 -> String) -> Word64 -> Markup
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> String
forall a. Show a => a -> String
show
    {-# INLINE toMarkup #-}

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

    -- | Convert a value to an attribute value without escaping
    --
    preEscapedToValue :: a -> AttributeValue
    preEscapedToValue = a -> AttributeValue
forall a. ToValue a => a -> AttributeValue
toValue
    {-# INLINE preEscapedToValue #-}

instance ToValue AttributeValue where
    toValue :: AttributeValue -> AttributeValue
toValue = AttributeValue -> AttributeValue
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 (String -> AttributeValue)
-> (Int -> String) -> Int -> AttributeValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String
forall a. Show a => a -> String
show
    {-# INLINE toValue #-}

instance ToValue Int32 where
    toValue :: Int32 -> AttributeValue
toValue = String -> AttributeValue
stringValue (String -> AttributeValue)
-> (Int32 -> String) -> Int32 -> AttributeValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int32 -> String
forall a. Show a => a -> String
show
    {-# INLINE toValue #-}

instance ToValue Int64 where
    toValue :: Int64 -> AttributeValue
toValue = String -> AttributeValue
stringValue (String -> AttributeValue)
-> (Int64 -> String) -> Int64 -> AttributeValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> String
forall a. Show a => a -> String
show
    {-# INLINE toValue #-}

instance ToValue Char where
    toValue :: Char -> AttributeValue
toValue = String -> AttributeValue
stringValue (String -> AttributeValue)
-> (Char -> String) -> Char -> AttributeValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> String
forall (m :: * -> *) a. Monad m => a -> m a
return
    {-# INLINE toValue #-}

instance ToValue Bool where
    toValue :: Bool -> AttributeValue
toValue = String -> AttributeValue
stringValue (String -> AttributeValue)
-> (Bool -> String) -> Bool -> AttributeValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> String
forall a. Show a => a -> String
show
    {-# INLINE toValue #-}

instance ToValue Integer where
    toValue :: Integer -> AttributeValue
toValue = String -> AttributeValue
stringValue (String -> AttributeValue)
-> (Integer -> String) -> Integer -> AttributeValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> String
forall a. Show a => a -> String
show
    {-# INLINE toValue #-}

instance ToValue Float where
    toValue :: Float -> AttributeValue
toValue = String -> AttributeValue
stringValue (String -> AttributeValue)
-> (Float -> String) -> Float -> AttributeValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Float -> String
forall a. Show a => a -> String
show
    {-# INLINE toValue #-}

instance ToValue Double where
    toValue :: Double -> AttributeValue
toValue = String -> AttributeValue
stringValue (String -> AttributeValue)
-> (Double -> String) -> Double -> AttributeValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> String
forall a. Show a => a -> String
show
    {-# INLINE toValue #-}

instance ToValue Word where
    toValue :: Word -> AttributeValue
toValue = String -> AttributeValue
stringValue (String -> AttributeValue)
-> (Word -> String) -> Word -> AttributeValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word -> String
forall a. Show a => a -> String
show
    {-# INLINE toValue #-}

instance ToValue Word32 where
    toValue :: Word32 -> AttributeValue
toValue = String -> AttributeValue
stringValue (String -> AttributeValue)
-> (Word32 -> String) -> Word32 -> AttributeValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> String
forall a. Show a => a -> String
show
    {-# INLINE toValue #-}

instance ToValue Word64 where
    toValue :: Word64 -> AttributeValue
toValue = String -> AttributeValue
stringValue (String -> AttributeValue)
-> (Word64 -> String) -> Word64 -> AttributeValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> String
forall a. Show a => a -> String
show
    {-# INLINE toValue #-}