{-# LANGUAGE CPP                        #-}
{-# LANGUAGE DeriveDataTypeable         #-}
{-# LANGUAGE ExistentialQuantification  #-}
{-# LANGUAGE FlexibleInstances          #-}
{-# LANGUAGE GADTs                      #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings          #-}
{-# LANGUAGE Rank2Types                 #-}
module Text.Blaze.Internal
    (
      
      ChoiceString (..)
    , StaticString (..)
    , MarkupM (..)
    , Markup
    , Tag
    , Attribute
    , AttributeValue
      
    , customParent
    , customLeaf
    , attribute
    , dataAttribute
    , customAttribute
      
    , text
    , preEscapedText
    , lazyText
    , preEscapedLazyText
    , textBuilder
    , preEscapedTextBuilder
    , string
    , preEscapedString
    , unsafeByteString
    , unsafeLazyByteString
      
    , textComment
    , lazyTextComment
    , stringComment
    , unsafeByteStringComment
    , unsafeLazyByteStringComment
      
    , textTag
    , stringTag
      
    , textValue
    , preEscapedTextValue
    , lazyTextValue
    , preEscapedLazyTextValue
    , textBuilderValue
    , preEscapedTextBuilderValue
    , stringValue
    , preEscapedStringValue
    , unsafeByteStringValue
    , unsafeLazyByteStringValue
      
    , Attributable
    , (!)
    , (!?)
      
    , contents
    , external
      
    , null
    ) where
import           Control.Applicative    (Applicative (..))
import qualified Data.List              as List
import           Data.Monoid            (Monoid, mappend, mconcat, mempty)
import           Prelude                hiding (null)
import qualified Data.ByteString        as B
import           Data.ByteString.Char8  (ByteString)
import qualified Data.ByteString.Lazy   as BL
import           Data.Text              (Text)
import qualified Data.Text              as T
import qualified Data.Text.Encoding     as T
import qualified Data.Text.Lazy         as LT
import qualified Data.Text.Lazy.Builder as LTB
import           Data.Typeable          (Typeable)
import           GHC.Exts               (IsString (..))
#if MIN_VERSION_base(4,9,0)
import           Data.Semigroup         (Semigroup(..))
#endif
data StaticString = StaticString
    { getString         :: String -> String  
    , getUtf8ByteString :: B.ByteString      
    , getText           :: Text              
    }
instance IsString StaticString where
    fromString s = let t = T.pack s
                   in StaticString (s ++) (T.encodeUtf8 t) t
data ChoiceString
    
    = Static {-# UNPACK #-} !StaticString
    
    | String String
    
    | Text Text
    
    | ByteString B.ByteString
    
    | PreEscaped ChoiceString
    
    | External ChoiceString
    
    | AppendChoiceString ChoiceString ChoiceString
    
    | EmptyChoiceString
#if MIN_VERSION_base(4,9,0)
instance Semigroup ChoiceString where
    (<>) = AppendChoiceString
    {-# INLINE (<>) #-}
#endif
instance Monoid ChoiceString where
    mempty = EmptyChoiceString
    {-# INLINE mempty #-}
#if !(MIN_VERSION_base(4,11,0))
    mappend = AppendChoiceString
    {-# INLINE mappend #-}
#endif
instance IsString ChoiceString where
    fromString = String
    {-# INLINE fromString #-}
data MarkupM a
    
    = Parent StaticString StaticString StaticString (MarkupM a)
    
    | CustomParent ChoiceString (MarkupM a)
    
    | Leaf StaticString StaticString StaticString a
    
    | CustomLeaf ChoiceString Bool a
    
    | Content ChoiceString a
    
    
    | Comment ChoiceString a
    
    | forall b. Append (MarkupM b) (MarkupM a)
    
    
    | AddAttribute StaticString StaticString ChoiceString (MarkupM a)
    
    | AddCustomAttribute ChoiceString ChoiceString (MarkupM a)
    
    | Empty a
    deriving (Typeable)
type Markup = MarkupM ()
instance Monoid a => Monoid (MarkupM a) where
    mempty = Empty mempty
    {-# INLINE mempty #-}
#if !(MIN_VERSION_base(4,11,0))
    mappend x y = Append x y
    {-# INLINE mappend #-}
    mconcat = foldr Append (Empty mempty)
    {-# INLINE mconcat #-}
#endif
#if MIN_VERSION_base(4,9,0)
instance Monoid a => Semigroup (MarkupM a) where
    x <> y = Append x y
    {-# INLINE (<>) #-}
    sconcat = foldr Append (Empty mempty)
    {-# INLINE sconcat #-}
#endif
instance Functor MarkupM where
    fmap f x =
        
        
        Append x (Empty (f (markupValue x)))
instance Applicative MarkupM where
    pure x = Empty x
    {-# INLINE pure #-}
    (<*>) x y =
        
        Append (Append x y) (Empty (markupValue x (markupValue y)))
    {-# INLINE (<*>) #-}
    (*>) = Append
    {-# INLINE (*>) #-}
    
    
instance Monad MarkupM where
    return x = Empty x
    {-# INLINE return #-}
    (>>) = Append
    {-# INLINE (>>) #-}
    h1 >>= f = Append h1 (f (markupValue h1))
    {-# INLINE (>>=) #-}
instance (a ~ ()) => IsString (MarkupM a) where
    fromString x = Content (fromString x) mempty
    {-# INLINE fromString #-}
markupValue :: MarkupM a -> a
markupValue m0 = case m0 of
    Parent _ _ _ m1           -> markupValue m1
    CustomParent _ m1         -> markupValue m1
    Leaf _ _ _ x              -> x
    CustomLeaf _ _ x          -> x
    Content _ x               -> x
    Comment _ x               -> x
    Append _ m1               -> markupValue m1
    AddAttribute _ _ _ m1     -> markupValue m1
    AddCustomAttribute _ _ m1 -> markupValue m1
    Empty x                   -> x
newtype Tag = Tag { unTag :: StaticString }
    deriving (IsString)
newtype Attribute = Attribute (forall a. MarkupM a -> MarkupM a)
#if MIN_VERSION_base(4,9,0)
instance Semigroup Attribute where
    Attribute f <> Attribute g = Attribute (g . f)
#endif
instance Monoid Attribute where
    mempty                            = Attribute id
#if !(MIN_VERSION_base(4,11,0))
    Attribute f `mappend` Attribute g = Attribute (g . f)
#endif
newtype AttributeValue = AttributeValue { unAttributeValue :: ChoiceString }
    deriving (IsString, Monoid
#if MIN_VERSION_base(4,9,0)
             ,Semigroup
#endif
             )
customParent :: Tag     
             -> Markup  
             -> Markup  
customParent tag cont = CustomParent (Static $ unTag tag) cont
customLeaf :: Tag     
           -> Bool    
           -> Markup  
customLeaf tag close = CustomLeaf (Static $ unTag tag) close ()
attribute :: Tag             
          -> Tag             
          -> AttributeValue  
          -> Attribute       
attribute rawKey key value = Attribute $
    AddAttribute (unTag rawKey) (unTag key) (unAttributeValue value)
{-# INLINE attribute #-}
dataAttribute :: Tag             
              -> AttributeValue  
              -> Attribute       
dataAttribute tag value = Attribute $ AddCustomAttribute
    (Static "data-" `mappend` Static (unTag tag))
    (unAttributeValue value)
{-# INLINE dataAttribute #-}
customAttribute :: Tag             
                -> AttributeValue  
                -> Attribute       
customAttribute tag value = Attribute $ AddCustomAttribute
    (Static $ unTag tag)
    (unAttributeValue value)
{-# INLINE customAttribute #-}
text :: Text    
     -> Markup  
text = content . Text
{-# INLINE text #-}
preEscapedText :: Text    
               -> Markup  
preEscapedText = content . PreEscaped . Text
{-# INLINE preEscapedText #-}
lazyText :: LT.Text  
         -> Markup   
lazyText = mconcat . map text . LT.toChunks
{-# INLINE lazyText #-}
preEscapedLazyText :: LT.Text  
                   -> Markup   
preEscapedLazyText = mconcat . map preEscapedText . LT.toChunks
{-# INLINE preEscapedLazyText #-}
textBuilder :: LTB.Builder 
            -> Markup      
textBuilder = lazyText . LTB.toLazyText
{-# INLINE textBuilder #-}
preEscapedTextBuilder :: LTB.Builder 
                      -> Markup      
preEscapedTextBuilder = preEscapedLazyText . LTB.toLazyText
{-# INLINE preEscapedTextBuilder #-}
content :: ChoiceString -> Markup
content cs = Content cs ()
{-# INLINE content #-}
string :: String  
       -> Markup  
string = content . String
{-# INLINE string #-}
preEscapedString :: String  
                 -> Markup  
preEscapedString = content . PreEscaped . String
{-# INLINE preEscapedString #-}
unsafeByteString :: ByteString  
                 -> Markup      
unsafeByteString = content . ByteString
{-# INLINE unsafeByteString #-}
unsafeLazyByteString :: BL.ByteString  
                     -> Markup         
unsafeLazyByteString = mconcat . map unsafeByteString . BL.toChunks
{-# INLINE unsafeLazyByteString #-}
comment :: ChoiceString -> Markup
comment cs = Comment cs ()
{-# INLINE comment #-}
textComment :: Text -> Markup
textComment = comment . PreEscaped . Text
lazyTextComment :: LT.Text -> Markup
lazyTextComment = comment . mconcat . map (PreEscaped . Text) . LT.toChunks
stringComment :: String -> Markup
stringComment = comment . PreEscaped . String
unsafeByteStringComment :: ByteString -> Markup
unsafeByteStringComment = comment . PreEscaped . ByteString
unsafeLazyByteStringComment :: BL.ByteString -> Markup
unsafeLazyByteStringComment =
    comment . mconcat . map (PreEscaped . ByteString) . BL.toChunks
textTag :: Text  
        -> Tag   
textTag t = Tag $ StaticString (T.unpack t ++) (T.encodeUtf8 t) t
stringTag :: String  
          -> Tag     
stringTag = Tag . fromString
textValue :: Text            
          -> AttributeValue  
textValue = AttributeValue . Text
{-# INLINE textValue #-}
preEscapedTextValue :: Text            
                    -> AttributeValue  
preEscapedTextValue = AttributeValue . PreEscaped . Text
{-# INLINE preEscapedTextValue #-}
lazyTextValue :: LT.Text         
              -> AttributeValue  
lazyTextValue = mconcat . map textValue . LT.toChunks
{-# INLINE lazyTextValue #-}
preEscapedLazyTextValue :: LT.Text         
                        -> AttributeValue  
preEscapedLazyTextValue = mconcat . map preEscapedTextValue . LT.toChunks
{-# INLINE preEscapedLazyTextValue #-}
textBuilderValue :: LTB.Builder    
                 -> AttributeValue 
textBuilderValue = lazyTextValue . LTB.toLazyText
{-# INLINE textBuilderValue #-}
preEscapedTextBuilderValue :: LTB.Builder    
                           -> AttributeValue 
preEscapedTextBuilderValue = preEscapedLazyTextValue . LTB.toLazyText
{-# INLINE preEscapedTextBuilderValue #-}
stringValue :: String -> AttributeValue
stringValue = AttributeValue . String
{-# INLINE stringValue #-}
preEscapedStringValue :: String -> AttributeValue
preEscapedStringValue = AttributeValue . PreEscaped . String
{-# INLINE preEscapedStringValue #-}
unsafeByteStringValue :: ByteString      
                      -> AttributeValue  
unsafeByteStringValue = AttributeValue . ByteString
{-# INLINE unsafeByteStringValue #-}
unsafeLazyByteStringValue :: BL.ByteString   
                          -> AttributeValue  
unsafeLazyByteStringValue = mconcat . map unsafeByteStringValue . BL.toChunks
{-# INLINE unsafeLazyByteStringValue #-}
class Attributable h where
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    (!) :: h -> Attribute -> h
instance Attributable (MarkupM a) where
    h ! (Attribute f) = f h
    {-# INLINE (!) #-}
instance Attributable (MarkupM a -> MarkupM b) where
    h ! f = (! f) . h
    {-# INLINE (!) #-}
(!?) :: Attributable h => h -> (Bool, Attribute) -> h
(!?) h (c, a) = if c then h ! a else h
external :: MarkupM a -> MarkupM a
external (Content x a)              = Content (External x) a
external (Append x y)               = Append (external x) (external y)
external (Parent x y z i)           = Parent x y z $ external i
external (CustomParent x i)         = CustomParent x $ external i
external (AddAttribute x y z i)     = AddAttribute x y z $ external i
external (AddCustomAttribute x y i) = AddCustomAttribute x y $ external i
external x                          = x
{-# INLINE external #-}
contents :: MarkupM a -> MarkupM a
contents (Parent _ _ _ c)           = contents c
contents (CustomParent _ c)         = contents c
contents (Content c x)              = Content c x
contents (Append c1 c2)             = Append (contents c1) (contents c2)
contents (AddAttribute _ _ _ c)     = contents c
contents (AddCustomAttribute _ _ c) = contents c
contents m                          = Empty (markupValue m)
null :: MarkupM a -> Bool
null markup = case markup of
    Parent _ _ _ _           -> False
    CustomParent _ _         -> False
    Leaf _ _ _ _             -> False
    CustomLeaf _ _ _         -> False
    Content c _              -> emptyChoiceString c
    Comment c _              -> emptyChoiceString c
    Append c1 c2             -> null c1 && null c2
    AddAttribute _ _ _ c     -> null c
    AddCustomAttribute _ _ c -> null c
    Empty _                  -> True
  where
    emptyChoiceString cs = case cs of
        Static ss                -> emptyStaticString ss
        String s                 -> List.null s
        Text t                   -> T.null t
        ByteString bs            -> B.null bs
        PreEscaped c             -> emptyChoiceString c
        External c               -> emptyChoiceString c
        AppendChoiceString c1 c2 -> emptyChoiceString c1 && emptyChoiceString c2
        EmptyChoiceString        -> True
    emptyStaticString = B.null . getUtf8ByteString