module Text.XML.HaXml.Escape(
xmlEscape,
xmlUnEscape,
xmlEscapeContent,
xmlUnEscapeContent,
XmlEscaper,
stdXmlEscaper,
mkXmlEscaper,
) where
import Data.Char
import Text.XML.HaXml.Types
#if __GLASGOW_HASKELL__ >= 604 || __NHC__ >= 118 || defined(__HUGS__)
import qualified Data.Map as Map
type FiniteMap a b = Map.Map a b
listToFM :: Ord a => [(a,b)] -> FiniteMap a b
listToFM :: forall a b. Ord a => [(a, b)] -> FiniteMap a b
listToFM = forall a b. Ord a => [(a, b)] -> FiniteMap a b
Map.fromList
lookupFM :: Ord a => FiniteMap a b -> a -> Maybe b
lookupFM :: forall a b. Ord a => FiniteMap a b -> a -> Maybe b
lookupFM = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup
#elif __GLASGOW_HASKELL__ >= 504 || __NHC__ > 114
import Data.FiniteMap
#else
type FiniteMap a b = [(a,b)]
listToFM :: Eq a => [(a,b)] -> FiniteMap a b
listToFM = id
lookupFM :: Eq a => FiniteMap a b -> a -> Maybe b
lookupFM fm k = lookup k fm
#endif
data XmlEscaper = XmlEscaper {
XmlEscaper -> FiniteMap Char String
toEscape :: FiniteMap Char String,
XmlEscaper -> FiniteMap String Char
fromEscape :: FiniteMap String Char,
XmlEscaper -> Char -> Bool
isEscape :: Char -> Bool
}
xmlEscape :: XmlEscaper -> Element i -> Element i
xmlEscape :: forall i. XmlEscaper -> Element i -> Element i
xmlEscape XmlEscaper
xmlEscaper Element i
element =
forall i. Element i -> Element i
compressElement (forall i. XmlEscaper -> Element i -> Element i
escapeElement XmlEscaper
xmlEscaper Element i
element)
xmlEscapeContent :: XmlEscaper -> [Content i] -> [Content i]
xmlEscapeContent :: forall i. XmlEscaper -> [Content i] -> [Content i]
xmlEscapeContent XmlEscaper
xmlEscaper [Content i]
cs =
forall i. [Content i] -> [Content i]
compressContent (forall i. XmlEscaper -> [Content i] -> [Content i]
escapeContent XmlEscaper
xmlEscaper [Content i]
cs)
escapeElement :: XmlEscaper -> Element i -> Element i
escapeElement :: forall i. XmlEscaper -> Element i -> Element i
escapeElement XmlEscaper
xmlEscaper (Elem QName
name [Attribute]
attributes [Content i]
content) =
forall i. QName -> [Attribute] -> [Content i] -> Element i
Elem QName
name (XmlEscaper -> [Attribute] -> [Attribute]
escapeAttributes XmlEscaper
xmlEscaper [Attribute]
attributes)
(forall i. XmlEscaper -> [Content i] -> [Content i]
escapeContent XmlEscaper
xmlEscaper [Content i]
content)
escapeAttributes :: XmlEscaper -> [Attribute] -> [Attribute]
escapeAttributes :: XmlEscaper -> [Attribute] -> [Attribute]
escapeAttributes XmlEscaper
xmlEscaper =
forall a b. (a -> b) -> [a] -> [b]
map (\ (QName
name,AttValue
av) -> (QName
name,XmlEscaper -> AttValue -> AttValue
escapeAttValue XmlEscaper
xmlEscaper AttValue
av))
escapeAttValue :: XmlEscaper -> AttValue -> AttValue
escapeAttValue :: XmlEscaper -> AttValue -> AttValue
escapeAttValue XmlEscaper
xmlEscaper (AttValue [Either String Reference]
attValList) =
[Either String Reference] -> AttValue
AttValue (
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap
(\ Either String Reference
av -> case Either String Reference
av of
Right Reference
_ -> [Either String Reference
av]
Left String
s ->
forall a b. (a -> b) -> [a] -> [b]
map
(\ Char
c -> if XmlEscaper -> Char -> Bool
isEscape XmlEscaper
xmlEscaper Char
c
then
forall a b. b -> Either a b
Right (XmlEscaper -> Char -> Reference
mkEscape XmlEscaper
xmlEscaper Char
c)
else
forall a b. a -> Either a b
Left [Char
c]
)
String
s
)
[Either String Reference]
attValList
)
escapeContent :: XmlEscaper -> [Content i] -> [Content i]
escapeContent :: forall i. XmlEscaper -> [Content i] -> [Content i]
escapeContent XmlEscaper
xmlEscaper =
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap
(\ Content i
content -> case Content i
content of
(CString Bool
b String
str i
i) ->
forall a b. (a -> b) -> [a] -> [b]
map
(\ Char
c -> if XmlEscaper -> Char -> Bool
isEscape XmlEscaper
xmlEscaper Char
c
then
forall i. Reference -> i -> Content i
CRef (XmlEscaper -> Char -> Reference
mkEscape XmlEscaper
xmlEscaper Char
c) i
i
else
forall i. Bool -> String -> i -> Content i
CString Bool
b [Char
c] i
i
)
String
str
(CElem Element i
element i
i) -> [forall i. Element i -> i -> Content i
CElem (forall i. XmlEscaper -> Element i -> Element i
escapeElement XmlEscaper
xmlEscaper Element i
element) i
i]
Content i
_ -> [Content i
content]
)
mkEscape :: XmlEscaper -> Char -> Reference
mkEscape :: XmlEscaper -> Char -> Reference
mkEscape (XmlEscaper {toEscape :: XmlEscaper -> FiniteMap Char String
toEscape = FiniteMap Char String
toescape}) Char
ch =
case forall a b. Ord a => FiniteMap a b -> a -> Maybe b
lookupFM FiniteMap Char String
toescape Char
ch of
Maybe String
Nothing -> Int -> Reference
RefChar (Char -> Int
ord Char
ch)
Just String
str -> String -> Reference
RefEntity String
str
xmlUnEscape :: XmlEscaper -> Element i -> Element i
xmlUnEscape :: forall i. XmlEscaper -> Element i -> Element i
xmlUnEscape XmlEscaper
xmlEscaper Element i
element =
forall i. Element i -> Element i
compressElement (forall i. XmlEscaper -> Element i -> Element i
unEscapeElement XmlEscaper
xmlEscaper Element i
element)
xmlUnEscapeContent :: XmlEscaper -> [Content i] -> [Content i]
xmlUnEscapeContent :: forall i. XmlEscaper -> [Content i] -> [Content i]
xmlUnEscapeContent XmlEscaper
xmlEscaper [Content i]
cs =
forall i. [Content i] -> [Content i]
compressContent (forall i. XmlEscaper -> [Content i] -> [Content i]
unEscapeContent XmlEscaper
xmlEscaper [Content i]
cs)
unEscapeElement :: XmlEscaper -> Element i -> Element i
unEscapeElement :: forall i. XmlEscaper -> Element i -> Element i
unEscapeElement XmlEscaper
xmlEscaper (Elem QName
name [Attribute]
attributes [Content i]
content) =
forall i. QName -> [Attribute] -> [Content i] -> Element i
Elem QName
name (XmlEscaper -> [Attribute] -> [Attribute]
unEscapeAttributes XmlEscaper
xmlEscaper [Attribute]
attributes)
(forall i. XmlEscaper -> [Content i] -> [Content i]
unEscapeContent XmlEscaper
xmlEscaper [Content i]
content)
unEscapeAttributes :: XmlEscaper -> [Attribute] -> [Attribute]
unEscapeAttributes :: XmlEscaper -> [Attribute] -> [Attribute]
unEscapeAttributes XmlEscaper
xmlEscaper =
forall a b. (a -> b) -> [a] -> [b]
map (\ (QName
name,AttValue
av) -> (QName
name,XmlEscaper -> AttValue -> AttValue
unEscapeAttValue XmlEscaper
xmlEscaper AttValue
av))
unEscapeAttValue :: XmlEscaper -> AttValue -> AttValue
unEscapeAttValue :: XmlEscaper -> AttValue -> AttValue
unEscapeAttValue XmlEscaper
xmlEscaper (AttValue [Either String Reference]
attValList) =
[Either String Reference] -> AttValue
AttValue (
forall a b. (a -> b) -> [a] -> [b]
map
(\ Either String Reference
av -> case Either String Reference
av of
Left String
_ -> Either String Reference
av
Right Reference
ref -> case XmlEscaper -> Reference -> Maybe Char
unEscapeChar XmlEscaper
xmlEscaper Reference
ref of
Just Char
c -> forall a b. a -> Either a b
Left [Char
c]
Maybe Char
Nothing -> Either String Reference
av
)
[Either String Reference]
attValList
)
unEscapeContent :: XmlEscaper -> [Content i] -> [Content i]
unEscapeContent :: forall i. XmlEscaper -> [Content i] -> [Content i]
unEscapeContent XmlEscaper
xmlEscaper =
forall a b. (a -> b) -> [a] -> [b]
map
(\ Content i
cntnt -> case Content i
cntnt of
CRef Reference
ref i
i -> case XmlEscaper -> Reference -> Maybe Char
unEscapeChar XmlEscaper
xmlEscaper Reference
ref of
Just Char
c -> forall i. Bool -> String -> i -> Content i
CString Bool
False [Char
c] i
i
Maybe Char
Nothing -> Content i
cntnt
CElem Element i
element i
i -> forall i. Element i -> i -> Content i
CElem (forall i. XmlEscaper -> Element i -> Element i
unEscapeElement XmlEscaper
xmlEscaper Element i
element) i
i
Content i
_ -> Content i
cntnt
)
unEscapeChar :: XmlEscaper -> Reference -> Maybe Char
unEscapeChar :: XmlEscaper -> Reference -> Maybe Char
unEscapeChar XmlEscaper
xmlEscaper Reference
ref =
case Reference
ref of
RefChar Int
i -> forall a. a -> Maybe a
Just (Int -> Char
chr Int
i)
RefEntity String
name -> forall a b. Ord a => FiniteMap a b -> a -> Maybe b
lookupFM (XmlEscaper -> FiniteMap String Char
fromEscape XmlEscaper
xmlEscaper) String
name
compressElement :: Element i -> Element i
compressElement :: forall i. Element i -> Element i
compressElement (Elem QName
name [Attribute]
attributes [Content i]
content) =
forall i. QName -> [Attribute] -> [Content i] -> Element i
Elem QName
name ([Attribute] -> [Attribute]
compressAttributes [Attribute]
attributes) (forall i. [Content i] -> [Content i]
compressContent [Content i]
content)
compressAttributes :: [(QName,AttValue)] -> [(QName,AttValue)]
compressAttributes :: [Attribute] -> [Attribute]
compressAttributes =
forall a b. (a -> b) -> [a] -> [b]
map (\ (QName
name,AttValue
av) -> (QName
name,AttValue -> AttValue
compressAttValue AttValue
av))
compressAttValue :: AttValue -> AttValue
compressAttValue :: AttValue -> AttValue
compressAttValue (AttValue [Either String Reference]
l) = [Either String Reference] -> AttValue
AttValue ([Either String Reference] -> [Either String Reference]
compress [Either String Reference]
l)
where
compress :: [Either String Reference] -> [Either String Reference]
compress :: [Either String Reference] -> [Either String Reference]
compress [] = []
compress (Right Reference
ref : [Either String Reference]
es) = forall a b. b -> Either a b
Right Reference
ref forall a. a -> [a] -> [a]
: [Either String Reference] -> [Either String Reference]
compress [Either String Reference]
es
compress ( ls :: Either String Reference
ls@(Left String
s1) : [Either String Reference]
es) =
case [Either String Reference] -> [Either String Reference]
compress [Either String Reference]
es of
(Left String
s2 : [Either String Reference]
es2) -> forall a b. a -> Either a b
Left (String
s1 forall a. [a] -> [a] -> [a]
++ String
s2) forall a. a -> [a] -> [a]
: [Either String Reference]
es2
[Either String Reference]
es2 -> Either String Reference
ls forall a. a -> [a] -> [a]
: [Either String Reference]
es2
compressContent :: [Content i] -> [Content i]
compressContent :: forall i. [Content i] -> [Content i]
compressContent [] = []
compressContent (csb :: Content i
csb@(CString Bool
b1 String
s1 i
i1) : [Content i]
cs) =
case forall i. [Content i] -> [Content i]
compressContent [Content i]
cs of
(CString Bool
b2 String
s2 i
_) : [Content i]
cs2
| Bool
b1 forall a. Eq a => a -> a -> Bool
== Bool
b2
-> forall i. Bool -> String -> i -> Content i
CString Bool
b1 (String
s1 forall a. [a] -> [a] -> [a]
++ String
s2) i
i1forall a. a -> [a] -> [a]
: [Content i]
cs2
[Content i]
cs2 -> Content i
csb forall a. a -> [a] -> [a]
: [Content i]
cs2
compressContent (CElem Element i
element i
i : [Content i]
cs) =
forall i. Element i -> i -> Content i
CElem (forall i. Element i -> Element i
compressElement Element i
element) i
i forall a. a -> [a] -> [a]
: forall i. [Content i] -> [Content i]
compressContent [Content i]
cs
compressContent (Content i
c : [Content i]
cs) = Content i
c forall a. a -> [a] -> [a]
: forall i. [Content i] -> [Content i]
compressContent [Content i]
cs
stdXmlEscaper :: XmlEscaper
stdXmlEscaper :: XmlEscaper
stdXmlEscaper = [(Char, String)] -> (Char -> Bool) -> XmlEscaper
mkXmlEscaper
[(Char
'\60',String
"lt"),(Char
'\62',String
"gt"),(Char
'\38',String
"amp"),(Char
'\39',String
"apos"),(Char
'\34',String
"quot")]
(\ Char
ch ->
let
i :: Int
i = Char -> Int
ord Char
ch
in
Int
i forall a. Ord a => a -> a -> Bool
< Int
10 Bool -> Bool -> Bool
|| (Int
10forall a. Ord a => a -> a -> Bool
<Int
i Bool -> Bool -> Bool
&& Int
iforall a. Ord a => a -> a -> Bool
<Int
32) Bool -> Bool -> Bool
|| Int
i forall a. Ord a => a -> a -> Bool
>= Int
127 Bool -> Bool -> Bool
||
case Char
ch of
Char
'\'' -> Bool
True
Char
'\"' -> Bool
True
Char
'&' -> Bool
True
Char
'<' -> Bool
True
Char
'>' -> Bool
True
Char
_ -> Bool
False
)
mkXmlEscaper :: [(Char,String)] -> (Char -> Bool) -> XmlEscaper
mkXmlEscaper :: [(Char, String)] -> (Char -> Bool) -> XmlEscaper
mkXmlEscaper [(Char, String)]
escapes Char -> Bool
isescape =
XmlEscaper {
toEscape :: FiniteMap Char String
toEscape = forall a b. Ord a => [(a, b)] -> FiniteMap a b
listToFM [(Char, String)]
escapes,
fromEscape :: FiniteMap String Char
fromEscape = forall a b. Ord a => [(a, b)] -> FiniteMap a b
listToFM (forall a b. (a -> b) -> [a] -> [b]
map (\ (Char
c,String
str) -> (String
str,Char
c)) [(Char, String)]
escapes),
isEscape :: Char -> Bool
isEscape = Char -> Bool
isescape
}