module Graphics.Svg.Core
(
Attribute
, Element
, ToElement(..)
, Term(..)
, makeAttribute
, makeElement
, makeElementNoEnd
, makeElementDoctype
, with
, renderBS
, renderToFile
, renderText
) where
import Blaze.ByteString.Builder (Builder)
import qualified Blaze.ByteString.Builder as BB
import qualified Blaze.ByteString.Builder.Html.Utf8 as BB
import qualified Data.ByteString.Lazy as LB
import Data.ByteString.Lazy (ByteString)
import Data.Hashable (Hashable(..))
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as M
import Data.Monoid
import Data.String
import Data.Text (Text)
import qualified Data.Text.Lazy as LT
import qualified Data.Text.Lazy.Encoding as LT
data Attribute = Attribute !Text !Text
deriving (Show,Eq)
instance Hashable Attribute where
hashWithSalt salt (Attribute a b) = salt `hashWithSalt` a `hashWithSalt` b
newtype Element = Element (HashMap Text Text -> Builder)
instance Show Element where
show e = LT.unpack . renderText $ e
instance Monoid Element where
mempty = Element mempty
mappend (Element e1) (Element e2) = Element (e1 <> e2)
instance IsString Element where
fromString = toElement
class ToElement a where
toElement :: a -> Element
instance ToElement String where
toElement = Element . const . BB.fromHtmlEscapedString
instance ToElement Text where
toElement = Element . const . BB.fromHtmlEscapedText
instance ToElement LT.Text where
toElement = Element . const . BB.fromHtmlEscapedLazyText
class Term result where
term :: Text -> [Attribute] -> result
instance (e ~ Element) => Term (e -> Element) where
term name attrs e = with (makeElement name e) attrs
instance Term Element where
term name attrs = with (makeElementNoEnd name) attrs
makeAttribute :: Text
-> Text
-> Attribute
makeAttribute = Attribute
unionAttrs :: HashMap Text Text -> HashMap Text Text -> HashMap Text Text
unionAttrs = M.unionWith (<>)
with :: Element -> [Attribute] -> Element
with (Element e) attrs = Element $ \a ->
e (unionAttrs (M.fromListWith (<>) (map toPair attrs)) a)
where
toPair (Attribute x y) = (x,y)
makeElement :: Text -> Element -> Element
makeElement name (Element c) = Element $ \a -> go c a
where
go children attrs =
s2b "<" <> BB.fromText name
<> foldlMapWithKey buildAttr attrs <> s2b ">"
<> children mempty
<> s2b "</" <> BB.fromText name <> s2b ">"
makeElementDoctype :: Text -> Element
makeElementDoctype name = Element $ \a -> go a
where
go attrs =
s2b "<" <> BB.fromText name
<> foldlMapWithKey buildAttr attrs <> s2b ">"
makeElementNoEnd :: Text -> Element
makeElementNoEnd name = Element $ \a -> go a
where
go attrs =
s2b "<" <> BB.fromText name
<> foldlMapWithKey buildAttr attrs <> s2b "/>"
foldlMapWithKey :: Monoid m => (k -> v -> m) -> HashMap k v -> m
foldlMapWithKey f = M.foldlWithKey' (\m k v -> m <> f k v) mempty
s2b :: String -> Builder
s2b = BB.fromString
buildAttr :: Text -> Text -> Builder
buildAttr key val =
s2b " " <>
BB.fromText key <>
if val == mempty
then mempty
else s2b "=\"" <> BB.fromHtmlEscapedText val <> s2b "\""
renderBS :: Element -> ByteString
renderBS (Element e) = BB.toLazyByteString $ e mempty
renderToFile :: FilePath -> Element -> IO ()
renderToFile fp = LB.writeFile fp . renderBS
renderText :: Element -> LT.Text
renderText = LT.decodeUtf8 . renderBS