module Text.XML.Basic.Entity (
Name,
list, listInternetExploder,
mapNameToChar, mapCharToName,
numberToChar,
) where
import qualified Data.Map as Map
import qualified Data.Char as Char
import Control.Monad.Exception.Synchronous (Exceptional, assert, throw, )
import Control.Monad.HT ((<=<), )
import Data.Monoid (Monoid(mempty, mappend), mconcat, )
import Data.Semigroup (Semigroup((<>)), )
import Data.Tuple.HT (swap, )
numberToChar :: String -> Exceptional String Char
numberToChar s =
fmap Char.chr $
case s of
('x':ds) -> readBounded 16 Char.isHexDigit ds
ds -> readBounded 10 Char.isDigit ds
readBounded :: Int -> (Char -> Bool) -> String -> Exceptional String Int
readBounded base validChar str =
case str of
"" -> throw "empty number string"
"0" -> return 0
_ ->
let m digit =
Update $ \mostSig ->
let n = mostSig*base + Char.digitToInt digit
in assert ("invalid character "++show digit)
(validChar digit) >>
assert "leading zero not allowed for security reasons"
(not (mostSig==0 && digit=='0')) >>
assert "number too big"
(n <= Char.ord maxBound) >>
return n
in evalUpdate (mconcat $ map m str) 0
newtype Update e a = Update {evalUpdate :: a -> Exceptional e a}
instance Semigroup (Update e a) where
Update x <> Update y = Update (y <=< x)
instance Monoid (Update e a) where
mempty = Update return
mappend = (<>)
type Name = String
mapNameToChar :: Map.Map Name Char
mapNameToChar =
Map.fromList list
mapCharToName :: Map.Map Char Name
mapCharToName =
Map.fromList $ map swap list
list :: [(Name, Char)]
list =
("apos", '\'') :
listInternetExploder
listInternetExploder :: [(Name, Char)]
listInternetExploder =
("quot", '"') :
("amp", '&') :
("lt", '<') :
("gt", '>') :
[]