module Html.Convert
( Converted(..)
, Convert(..)
) where
import Html.Type.Internal
import Data.Word
import Data.Proxy
import Data.String
import Data.Char (ord)
import Data.Double.Conversion.ByteString
import GHC.TypeLits
import GHC.Types
import GHC.Prim (Addr#, ord#, indexCharOffAddr#)
import GHC.CString (unpackCString#, unpackCStringUtf8#)
import qualified Data.Semigroup as S
import qualified Data.Monoid as M
import qualified Data.ByteString.Builder as B
import qualified Data.ByteString.Builder.Prim as BP
import qualified Data.ByteString.Builder.Internal as U
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Encoding as TL
escapeUtf8 :: BP.BoundedPrim Char
escapeUtf8 =
BP.condB (> '>' ) BP.charUtf8 $
BP.condB (== '<' ) (fixed4 ('&',('l',('t',';')))) $
BP.condB (== '>' ) (fixed4 ('&',('g',('t',';')))) $
BP.condB (== '&' ) (fixed5 ('&',('a',('m',('p',';'))))) $
BP.condB (== '"' ) (fixed5 ('&',('#',('3',('4',';'))))) $
BP.condB (== '\'') (fixed5 ('&',('#',('3',('9',';'))))) $
BP.liftFixedToBounded BP.char7
where
fixed4 x = BP.liftFixedToBounded $ const x BP.>$<
BP.char7 BP.>*< BP.char7 BP.>*< BP.char7 BP.>*< BP.char7
fixed5 x = BP.liftFixedToBounded $ const x BP.>$<
BP.char7 BP.>*< BP.char7 BP.>*< BP.char7 BP.>*< BP.char7 BP.>*< BP.char7
escape :: BP.BoundedPrim Word8
escape =
BP.condB (> c2w '>' ) (BP.liftFixedToBounded BP.word8) $
BP.condB (== c2w '<' ) (fixed4 (c2w '&',(c2w 'l',(c2w 't',c2w ';')))) $
BP.condB (== c2w '>' ) (fixed4 (c2w '&',(c2w 'g',(c2w 't',c2w ';')))) $
BP.condB (== c2w '&' ) (fixed5 (c2w '&',(c2w 'a',(c2w 'm',(c2w 'p',c2w ';'))))) $
BP.condB (== c2w '"' ) (fixed5 (c2w '&',(c2w '#',(c2w '3',(c2w '4',c2w ';'))))) $
BP.condB (== c2w '\'') (fixed5 (c2w '&',(c2w '#',(c2w '3',(c2w '9',c2w ';'))))) $
BP.liftFixedToBounded BP.word8
where
c2w = fromIntegral . ord
fixed4 x = BP.liftFixedToBounded $ const x BP.>$<
BP.word8 BP.>*< BP.word8 BP.>*< BP.word8 BP.>*< BP.word8
fixed5 x = BP.liftFixedToBounded $ const x BP.>$<
BP.word8 BP.>*< BP.word8 BP.>*< BP.word8 BP.>*< BP.word8 BP.>*< BP.word8
newtype Converted = Converted {unConv :: B.Builder} deriving (M.Monoid,S.Semigroup)
instance IsString Converted where
fromString = convert
class Convert a where
convert :: a -> Converted
instance Convert () where
convert _ = mempty
instance Convert b => Convert (a := b) where
convert (AT x) = convert x
instance Convert (Raw Char) where
convert (Raw c) = Converted (B.charUtf8 c)
instance Convert (Raw String) where
convert (Raw x) = stringConvRaw x
instance Convert (Raw T.Text) where
convert (Raw x) = Converted (T.encodeUtf8Builder x)
instance Convert (Raw TL.Text) where
convert (Raw x) = Converted (TL.encodeUtf8Builder x)
instance Convert (Raw B.Builder) where
convert (Raw x) = Converted x
instance Convert Char where
convert = Converted . BP.primBounded escapeUtf8
instance Convert String where
convert = stringConv
instance Convert T.Text where
convert = Converted . T.encodeUtf8BuilderEscaped escape
instance Convert TL.Text where
convert = Converted . TL.encodeUtf8BuilderEscaped escape
instance Convert Int where
convert = Converted . B.intDec
instance Convert Integer where
convert = Converted . B.integerDec
instance Convert Float where
convert = Converted . U.byteStringCopy . toShortest . realToFrac
instance Convert Double where
convert = Converted . U.byteStringCopy . toShortest
instance Convert Word where
convert = Converted . B.wordDec
instance KnownSymbol a => Convert (Proxy a) where
convert = Converted . U.byteStringCopy . fromString . symbolVal
instance ConcatSymbol xs => Convert (Proxy (xs :: [Symbol])) where
convert = Converted . U.byteStringCopy . fromString . concatSymbol
class ConcatSymbol (xs :: [Symbol]) where
concatSymbol :: Proxy xs -> String
instance (KnownSymbol x, ConcatSymbol xs) => ConcatSymbol (x ': xs) where
concatSymbol _ = symbolVal (Proxy :: Proxy x) ++ concatSymbol (Proxy :: Proxy xs)
instance ConcatSymbol '[] where
concatSymbol _ = mempty
builderCString# :: BP.BoundedPrim Word8 -> Addr# -> Converted
builderCString# bp addr = Converted $ BP.primUnfoldrBounded bp go 0
where
go !i | b /= 0 = Just (fromIntegral b, i+1)
| otherwise = Nothing
where
!b = I# (ord# (at# i))
at# (I# i#) = indexCharOffAddr# addr i#
stringConv :: String -> Converted
stringConv = Converted . BP.primMapListBounded escapeUtf8
stringConvRaw :: String -> Converted
stringConvRaw = Converted . B.stringUtf8