module Text.HTML.Moe2.Element where import Text.HTML.Moe2.Type import Text.HTML.Moe2.Utils import Data.Default import Control.Monad.Writer import Prelude hiding (id, span, div, head, (>), (.), (-)) import Air.Light ((-), first) import Data.DList (singleton, toList) import Data.Maybe (fromMaybe) element :: String -> MoeCombinator element x u = tell - singleton - def { name = pack - escape x , elements = toList - execWriter - u } (!) :: (MoeUnit -> MoeUnit) -> [Attribute] -> (MoeUnit -> MoeUnit) (!) = add_attributes infixl 1 ! add_attributes :: (MoeUnit -> MoeUnit) -> [Attribute] -> (MoeUnit -> MoeUnit) add_attributes f xs = \u -> let r = f u in tell - singleton - Attributes xs - fromMaybe def - first - toList - execWriter - r e :: String -> MoeCombinator e = element no_indent_element :: String -> MoeCombinator no_indent_element x u = tell - singleton - def { name = pack - x , elements = toList - execWriter u , indent = False } ne :: String -> MoeCombinator ne = no_indent_element self_close_element :: String -> LightCombinator self_close_element x _ = tell - singleton - def { name = pack - escape x , self_close = True } sc :: String -> LightCombinator sc = self_close_element str, raw, _pre, prim :: String -> MoeUnit no_escape_no_indent_str, escape_no_indent_str, no_escape_indent_str :: String -> MoeUnit no_escape_no_indent_str = raw escape_no_indent_str = _pre no_escape_indent_str = prim str x = tell - singleton - Data (pack - escape x) raw x = tell - singleton - Raw (pack x) _pre x = tell - singleton - Pre (pack - escape x) prim x = tell - singleton - Prim (pack x) raw_bytestring x = tell - singleton - Raw x prim_bytestring x = tell - singleton - Prim x