{-# LANGUAGE OverloadedStrings, GeneralizedNewtypeDeriving, Rank2Types,
FlexibleInstances, ExistentialQuantification,
DeriveDataTypeable, MultiParamTypeClasses, DeriveFunctor,
FunctionalDependencies #-}
module Text.Blaze.Front.Internal
(
ChoiceString (..)
, StaticString (..)
, MarkupM (..)
, Markup
, Tag
, Attribute (..)
, AttributeValue(..)
, customParent
, customLeaf
, attribute
, dataAttribute
, customAttribute
, text
, preEscapedText
, lazyText
, preEscapedLazyText
, string
, preEscapedString
, unsafeByteString
, unsafeLazyByteString
, textTag
, stringTag
, textValue
, preEscapedTextValue
, lazyTextValue
, preEscapedLazyTextValue
, stringValue
, preEscapedStringValue
, unsafeByteStringValue
, unsafeLazyByteStringValue
, Attributable
, (!)
, (!?)
, contents
, external
, null
) where
import Control.Applicative
import Data.ByteString.Char8 (ByteString)
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as BL
import qualified Data.List as List
import Data.Monoid (Monoid, mempty)
import Data.Semigroup (Semigroup, sconcat)
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 Data.Typeable (Typeable)
import GHC.Exts (IsString (..))
import Prelude hiding (null)
import Bridge
import Text.Blaze.Internal (StaticString(..), ChoiceString(..))
import Unsafe.Coerce (unsafeCoerce)
data MarkupM act a
= forall act'. MapActions (act' -> act) (MarkupM act' a)
| OnEvent (EventHandler act) (MarkupM act a)
| Parent StaticString StaticString StaticString (MarkupM act a)
| CustomParent ChoiceString (MarkupM act a)
| Leaf StaticString StaticString StaticString
| CustomLeaf ChoiceString Bool
| Content ChoiceString
| forall b c. Append (MarkupM act b) (MarkupM act c)
| AddAttribute StaticString StaticString ChoiceString (MarkupM act a)
| AddCustomAttribute ChoiceString ChoiceString (MarkupM act a)
| Empty
deriving (Typeable)
type Markup e = MarkupM e ()
instance Monoid a => Monoid (MarkupM ev a) where
mempty = Empty
{-# INLINE mempty #-}
instance Semigroup a => Semigroup (MarkupM ev a) where
x <> y = Append x y
{-# INLINE (<>) #-}
sconcat = foldr Append Empty
{-# INLINE sconcat #-}
instance Functor (MarkupM ev) where
fmap _ = unsafeCoerce
instance Applicative (MarkupM ev) where
pure _ = Empty
ff <*> fx = Append ff fx
instance Monad (MarkupM ev) where
return _ = Empty
{-# INLINE return #-}
(>>) = Append
{-# INLINE (>>) #-}
h1 >>= f = h1 >> f
(error "Text.Blaze.Internal.MarkupM: invalid use of monadic bind")
{-# INLINE (>>=) #-}
instance IsString (MarkupM ev a) where
fromString = Content . fromString
{-# INLINE fromString #-}
newtype Tag = Tag { unTag :: StaticString }
deriving (IsString)
newtype Attribute ev = Attribute (forall a. MarkupM ev a -> MarkupM ev a)
instance Monoid (Attribute ev) where
mempty = Attribute id
instance Semigroup (Attribute ev) where
Attribute f <> Attribute g = Attribute (g . f)
newtype AttributeValue = AttributeValue { unAttributeValue :: ChoiceString }
deriving (IsString, Monoid, Semigroup)
customParent :: Tag
-> Markup ev
-> Markup ev
customParent tag = CustomParent (Static $ unTag tag)
customLeaf :: Tag
-> Bool
-> Markup ev
customLeaf tag = CustomLeaf (Static $ unTag tag)
attribute :: Tag
-> Tag
-> AttributeValue
-> Attribute ev
attribute rawKey key value = Attribute $
AddAttribute (unTag rawKey) (unTag key) (unAttributeValue value)
{-# INLINE attribute #-}
dataAttribute :: Tag
-> AttributeValue
-> Attribute ev
dataAttribute tag value = Attribute $ AddCustomAttribute
(Static "data-" `mappend` Static (unTag tag))
(unAttributeValue value)
{-# INLINE dataAttribute #-}
customAttribute :: Tag
-> AttributeValue
-> Attribute ev
customAttribute tag value = Attribute $ AddCustomAttribute
(Static $ unTag tag)
(unAttributeValue value)
{-# INLINE customAttribute #-}
text :: Text
-> Markup ev
text = Content . Text
{-# INLINE text #-}
preEscapedText :: Text
-> Markup ev
preEscapedText = Content . PreEscaped . Text
{-# INLINE preEscapedText #-}
lazyText :: LT.Text
-> Markup ev
lazyText = mconcat . map text . LT.toChunks
{-# INLINE lazyText #-}
preEscapedLazyText :: LT.Text
-> Markup ev
preEscapedLazyText = mconcat . map preEscapedText . LT.toChunks
string :: String
-> Markup ev
string = Content . String
{-# INLINE string #-}
preEscapedString :: String
-> Markup ev
preEscapedString = Content . PreEscaped . String
{-# INLINE preEscapedString #-}
unsafeByteString :: ByteString
-> Markup ev
unsafeByteString = Content . ByteString
{-# INLINE unsafeByteString #-}
unsafeLazyByteString :: BL.ByteString
-> Markup ev
unsafeLazyByteString = mconcat . map unsafeByteString . BL.toChunks
{-# INLINE unsafeLazyByteString #-}
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 #-}
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 ev | h -> ev where
(!) :: h -> Attribute ev -> h
instance Attributable (MarkupM ev a) ev where
h ! (Attribute f) = f h
{-# INLINE (!) #-}
instance Attributable (MarkupM ev a -> MarkupM ev b) ev where
h ! f = (! f) . h
{-# INLINE (!) #-}
(!?) :: Attributable h ev => h -> (Bool, Attribute ev) -> h
(!?) h (c, a) = if c then h ! a else h
external :: MarkupM ev a -> MarkupM ev a
external (MapActions f x) = MapActions f (external x)
external (OnEvent ev x) = OnEvent ev (external x)
external (Content x) = Content $ External x
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
{-# INLINABLE external #-}
contents :: MarkupM ev a -> MarkupM ev' b
contents (MapActions _ c) = contents c
contents (OnEvent _ c) = contents c
contents (Parent _ _ _ c) = contents c
contents (CustomParent _ c) = contents c
contents (Content c) = Content c
contents (Append c1 c2) = Append (contents c1) (contents c2)
contents (AddAttribute _ _ _ c) = contents c
contents (AddCustomAttribute _ _ c) = contents c
contents _ = Empty
null :: MarkupM ev a -> Bool
null markup = case markup of
MapActions _ c -> null c
OnEvent _ c -> null c
Parent _ _ _ _ -> False
CustomParent _ _ -> False
Leaf _ _ _ -> False
CustomLeaf _ _ -> False
Content 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