{-# LANGUAGE OverloadedStrings #-} module Network.Damn.Format.Damn.Internal ( textToBytes , damnFormat' ) where import Data.ByteString (ByteString) import Data.ByteString.Builder import qualified Data.ByteString.Lazy as LB (toStrict) import Data.Char import Data.Monoid import Data.Text (Text) import qualified Data.Text import Network.Damn.Tablumps.TH textToBytes :: Text -> ByteString textToBytes = LB.toStrict . toLazyByteString . Data.Text.foldr (\c b -> maybeEscape c <> b) "" where maybeEscape c | ord c <= 127 = word8 (fromIntegral $ ord c) | otherwise = "&#x" <> word32Hex (fromIntegral $ ord c) <> ";" damnFormat' :: Lump -> ByteString damnFormat' (A x y) = " x <> "\" title=\"" <> y <> "\">" damnFormat' C_A = "" damnFormat' (Abbr x) = " x <> "\">" damnFormat' C_Abbr = "" damnFormat' (Acro x) = " x <> "\">" damnFormat' C_Acro = "" damnFormat' (Avatar x _) = ":icon" <> x <> ":" damnFormat' B = "" damnFormat' C_B = "" damnFormat' Bcode = "" damnFormat' C_Bcode = "" damnFormat' Br = "
" damnFormat' Code = "" damnFormat' C_Code = "" damnFormat' (Dev _ x) = ":dev" <> x <> ":" damnFormat' (Embed x y z) = " x <> "\" height=\"" <> y <> "\" width=\"" <> z <> "\">" damnFormat' C_Embed = "" damnFormat' (Emote x _ _ _ _) = x damnFormat' I = "" damnFormat' C_I = "" damnFormat' (Iframe x y z) = "" damnFormat' (Img x y z) = " x <> "\" height=\"" <> y <> "\" width=\"" <> z <> "\">" damnFormat' Li = "
  • " damnFormat' C_Li = "
  • " damnFormat' (Link x _) = x damnFormat' Ol = "
      " damnFormat' C_Ol = "
    " damnFormat' P = "

    " damnFormat' C_P = "

    " damnFormat' S = "" damnFormat' C_S = "" damnFormat' Sub = "" damnFormat' C_Sub = "" damnFormat' Sup = "" damnFormat' C_Sup = "" damnFormat' (Thumb x _ _ _ _ _) = ":thumb" <> x <> ":" damnFormat' U = "" damnFormat' C_U = "" damnFormat' Ul = ""