{-# LANGUAGE CPP #-}
module Text.XML.HaXml.Schema.PrettyHsBoot
( ppComment
, ppModule
, ppHighLevelDecl
, ppHighLevelDecls
, ppvList
) where
#if MIN_VERSION_base(4,11,0)
import Prelude hiding ((<>))
#endif
import Text.XML.HaXml.Types (QName(..),Namespace(..))
import Text.XML.HaXml.Schema.HaskellTypeModel
import Text.XML.HaXml.Schema.XSDTypeModel (Occurs(..))
import Text.XML.HaXml.Schema.NameConversion
import Text.PrettyPrint.HughesPJ as PP
import Data.List (intersperse,notElem,inits)
import Data.Maybe (isJust,fromJust,catMaybes)
ppvList :: String -> String -> String -> (a->Doc) -> [a] -> Doc
ppvList :: forall a. String -> String -> String -> (a -> Doc) -> [a] -> Doc
ppvList String
open String
sep String
close a -> Doc
pp [] = String -> Doc
text String
open Doc -> Doc -> Doc
<> String -> Doc
text String
close
ppvList String
open String
sep String
close a -> Doc
pp (a
x:[a]
xs) = String -> Doc
text String
open Doc -> Doc -> Doc
<+> a -> Doc
pp a
x
Doc -> Doc -> Doc
$$ [Doc] -> Doc
vcat (forall a b. (a -> b) -> [a] -> [b]
map (\a
y-> String -> Doc
text String
sep Doc -> Doc -> Doc
<+> a -> Doc
pp a
y) [a]
xs)
Doc -> Doc -> Doc
$$ String -> Doc
text String
close
data = Before | After
ppComment :: CommentPosition -> Comment -> Doc
CommentPosition
_ Comment
Nothing = Doc
empty
ppComment CommentPosition
pos (Just String
s) =
String -> Doc
text String
"--" Doc -> Doc -> Doc
<+> String -> Doc
text (case CommentPosition
pos of CommentPosition
Before -> String
"|"; CommentPosition
After -> String
"^") Doc -> Doc -> Doc
<+> String -> Doc
text String
c
Doc -> Doc -> Doc
$$
[Doc] -> Doc
vcat (forall a b. (a -> b) -> [a] -> [b]
map (\String
x-> String -> Doc
text String
"-- " Doc -> Doc -> Doc
<+> String -> Doc
text String
x) [String]
cs)
where
(String
c:[String]
cs) = String -> [String]
lines (Int -> String -> String
paragraph Int
60 String
s)
ppHName :: HName -> Doc
ppHName :: HName -> Doc
ppHName (HName String
x) = String -> Doc
text String
x
ppXName :: XName -> Doc
ppXName :: XName -> Doc
ppXName (XName (N String
x)) = String -> Doc
text String
x
ppXName (XName (QN Namespace
ns String
x)) = String -> Doc
text (Namespace -> String
nsPrefix Namespace
ns) Doc -> Doc -> Doc
<> String -> Doc
text String
":" Doc -> Doc -> Doc
<> String -> Doc
text String
x
ppModId, ppConId, ppVarId, ppUnqConId, ppUnqVarId, ppFwdConId
:: NameConverter -> XName -> Doc
ppModId :: NameConverter -> XName -> Doc
ppModId NameConverter
nx = HName -> Doc
ppHName forall b c a. (b -> c) -> (a -> b) -> a -> c
. NameConverter -> XName -> HName
modid NameConverter
nx
ppConId :: NameConverter -> XName -> Doc
ppConId NameConverter
nx = HName -> Doc
ppHName forall b c a. (b -> c) -> (a -> b) -> a -> c
. NameConverter -> XName -> HName
conid NameConverter
nx
ppVarId :: NameConverter -> XName -> Doc
ppVarId NameConverter
nx = HName -> Doc
ppHName forall b c a. (b -> c) -> (a -> b) -> a -> c
. NameConverter -> XName -> HName
varid NameConverter
nx
ppUnqConId :: NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx = HName -> Doc
ppHName forall b c a. (b -> c) -> (a -> b) -> a -> c
. NameConverter -> XName -> HName
unqconid NameConverter
nx
ppUnqVarId :: NameConverter -> XName -> Doc
ppUnqVarId NameConverter
nx = HName -> Doc
ppHName forall b c a. (b -> c) -> (a -> b) -> a -> c
. NameConverter -> XName -> HName
unqvarid NameConverter
nx
ppFwdConId :: NameConverter -> XName -> Doc
ppFwdConId NameConverter
nx = HName -> Doc
ppHName forall b c a. (b -> c) -> (a -> b) -> a -> c
. NameConverter -> XName -> HName
fwdconid NameConverter
nx
ppJoinConId, ppFieldId :: NameConverter -> XName -> XName -> Doc
ppJoinConId :: NameConverter -> XName -> XName -> Doc
ppJoinConId NameConverter
nx XName
p XName
q = HName -> Doc
ppHName (NameConverter -> XName -> HName
conid NameConverter
nx XName
p) Doc -> Doc -> Doc
<> String -> Doc
text String
"_" Doc -> Doc -> Doc
<> HName -> Doc
ppHName (NameConverter -> XName -> HName
conid NameConverter
nx XName
q)
ppFieldId :: NameConverter -> XName -> XName -> Doc
ppFieldId NameConverter
nx XName
t = HName -> Doc
ppHName forall b c a. (b -> c) -> (a -> b) -> a -> c
. NameConverter -> XName -> XName -> HName
fieldid NameConverter
nx XName
t
ppModule :: NameConverter -> Module -> Doc
ppModule :: NameConverter -> Module -> Doc
ppModule NameConverter
nx Module
m =
String -> Doc
text String
"{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-}"
Doc -> Doc -> Doc
$$ String -> Doc
text String
"{-# OPTIONS_GHC -fno-warn-duplicate-exports #-}"
Doc -> Doc -> Doc
$$ String -> Doc
text String
"module" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppModId NameConverter
nx (Module -> XName
module_name Module
m)
Doc -> Doc -> Doc
$$ Int -> Doc -> Doc
nest Int
2 (String -> Doc
text String
"( module" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppModId NameConverter
nx (Module -> XName
module_name Module
m)
Doc -> Doc -> Doc
$$ [Doc] -> Doc
vcat (forall a b. (a -> b) -> [a] -> [b]
map (\(XSDInclude XName
ex Comment
com)->
CommentPosition -> Comment -> Doc
ppComment CommentPosition
Before Comment
com
Doc -> Doc -> Doc
$$ String -> Doc
text String
", module" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppModId NameConverter
nx XName
ex)
(Module -> [Decl]
module_re_exports Module
m))
Doc -> Doc -> Doc
$$ String -> Doc
text String
") where")
Doc -> Doc -> Doc
$$ String -> Doc
text String
" "
Doc -> Doc -> Doc
$$ String -> Doc
text String
"import Text.XML.HaXml.Schema.Schema (SchemaType(..),SimpleType(..),Extension(..),Restricts(..))"
Doc -> Doc -> Doc
$$ String -> Doc
text String
"import Text.XML.HaXml.Schema.Schema as Schema"
Doc -> Doc -> Doc
$$ (case Module -> Maybe XName
module_xsd_ns Module
m of
Maybe XName
Nothing -> String -> Doc
text String
"import Text.XML.HaXml.Schema.PrimitiveTypes as Xsd"
Just XName
ns -> String -> Doc
text String
"import qualified Text.XML.HaXml.Schema.PrimitiveTypes as"Doc -> Doc -> Doc
<+>NameConverter -> XName -> Doc
ppConId NameConverter
nx XName
ns)
Doc -> Doc -> Doc
$$ [Doc] -> Doc
vcat (forall a b. (a -> b) -> [a] -> [b]
map (NameConverter -> Decl -> Doc
ppHighLevelDecl NameConverter
nx)
(Module -> [Decl]
module_re_exports Module
m ))
Doc -> Doc -> Doc
$$ String -> Doc
text String
" "
Doc -> Doc -> Doc
$$ NameConverter -> [Decl] -> Doc
ppHighLevelDecls NameConverter
nx (Module -> [Decl]
module_decls Module
m)
ppAttr :: Attribute -> Int -> Doc
ppAttr :: Attribute -> Int -> Doc
ppAttr Attribute
a Int
n = (String -> Doc
text String
"a"Doc -> Doc -> Doc
<>String -> Doc
text (forall a. Show a => a -> String
show Int
n)) Doc -> Doc -> Doc
<+> String -> Doc
text String
"<- getAttribute \""
Doc -> Doc -> Doc
<> XName -> Doc
ppXName (Attribute -> XName
attr_name Attribute
a)
Doc -> Doc -> Doc
<> String -> Doc
text String
"\" e pos"
ppElem :: NameConverter -> Element -> Doc
ppElem :: NameConverter -> Element -> Doc
ppElem NameConverter
nx e :: Element
e@Element{}
| Element -> Bool
elem_byRef Element
e = Modifier -> Doc -> Doc
ppElemModifier (Element -> Modifier
elem_modifier Element
e)
(String -> Doc
text String
"element"
Doc -> Doc -> Doc
<> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx (Element -> XName
elem_name Element
e))
| Bool
otherwise = Modifier -> Doc -> Doc
ppElemModifier (Element -> Modifier
elem_modifier Element
e)
(String -> Doc
text String
"parseSchemaType \""
Doc -> Doc -> Doc
<> XName -> Doc
ppXName (Element -> XName
elem_name Element
e)
Doc -> Doc -> Doc
<> String -> Doc
text String
"\"")
ppElem NameConverter
nx e :: Element
e@AnyElem{} = Modifier -> Doc -> Doc
ppElemModifier (Element -> Modifier
elem_modifier Element
e)
(String -> Doc
text String
"parseAnyElement")
ppElem NameConverter
nx e :: Element
e@Text{} = String -> Doc
text String
"parseText"
ppElem NameConverter
nx e :: Element
e@OneOf{} = Modifier -> Doc -> Doc
ppElemModifier (Element -> Modifier
elem_modifier Element
e)
(String -> Doc
text String
"oneOf" Doc -> Doc -> Doc
<+> forall a. String -> String -> String -> (a -> Doc) -> [a] -> Doc
ppvList String
"[" String
"," String
"]"
(forall {a}. Show a => a -> ([Element], Int) -> Doc
ppOneOf Int
n)
(forall a b. [a] -> [b] -> [(a, b)]
zip (Element -> [[Element]]
elem_oneOf Element
e) [Int
1..Int
n]))
where
n :: Int
n = forall (t :: * -> *) a. Foldable t => t a -> Int
length (Element -> [[Element]]
elem_oneOf Element
e)
ppOneOf :: a -> ([Element], Int) -> Doc
ppOneOf a
n ([Element]
e,Int
i) = String -> Doc
text String
"fmap" Doc -> Doc -> Doc
<+> String -> Doc
text (Int -> String
ordinal Int
i forall a. [a] -> [a] -> [a]
++String
"Of"forall a. [a] -> [a] -> [a]
++forall a. Show a => a -> String
show a
n)
Doc -> Doc -> Doc
<+> Doc -> Doc
parens ([Element] -> Doc
ppSeqElem [Element]
e)
ordinal :: Int -> String
ordinal Int
i | Int
i forall a. Ord a => a -> a -> Bool
<= Int
20 = [String]
ordinalsforall a. [a] -> Int -> a
!!Int
i
| Bool
otherwise = String
"Choice" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
i
ordinals :: [String]
ordinals = [String
"Zero",String
"One",String
"Two",String
"Three",String
"Four",String
"Five",String
"Six",String
"Seven",String
"Eight"
,String
"Nine",String
"Ten",String
"Eleven",String
"Twelve",String
"Thirteen",String
"Fourteen",String
"Fifteen"
,String
"Sixteen",String
"Seventeen",String
"Eighteen",String
"Nineteen",String
"Twenty"]
ppSeqElem :: [Element] -> Doc
ppSeqElem [] = Doc
PP.empty
ppSeqElem [Element
e] = NameConverter -> Element -> Doc
ppElem NameConverter
nx Element
e
ppSeqElem [Element]
es = String -> Doc
text (String
"return ("forall a. [a] -> [a] -> [a]
++forall a. Int -> a -> [a]
replicate (forall (t :: * -> *) a. Foldable t => t a -> Int
length [Element]
esforall a. Num a => a -> a -> a
-Int
1) Char
','forall a. [a] -> [a] -> [a]
++String
")")
Doc -> Doc -> Doc
<+> [Doc] -> Doc
vcat (forall a b. (a -> b) -> [a] -> [b]
map (\Element
e-> String -> Doc
text String
"`apply`" Doc -> Doc -> Doc
<+> NameConverter -> Element -> Doc
ppElem NameConverter
nx Element
e) [Element]
es)
ppHighLevelDecls :: NameConverter -> [Decl] -> Doc
ppHighLevelDecls :: NameConverter -> [Decl] -> Doc
ppHighLevelDecls NameConverter
nx [Decl]
hs = [Doc] -> Doc
vcat (forall a. a -> [a] -> [a]
intersperse (String -> Doc
text String
" ")
(forall a b. (a -> b) -> [a] -> [b]
map (NameConverter -> Decl -> Doc
ppHighLevelDecl NameConverter
nx) [Decl]
hs))
ppHighLevelDecl :: NameConverter -> Decl -> Doc
ppHighLevelDecl :: NameConverter -> Decl -> Doc
ppHighLevelDecl NameConverter
nx (NamedSimpleType XName
t XName
s Comment
comm) =
CommentPosition -> Comment -> Doc
ppComment CommentPosition
Before Comment
comm
Doc -> Doc -> Doc
$$ String -> Doc
text String
"type" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t Doc -> Doc -> Doc
<+> String -> Doc
text String
"=" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppConId NameConverter
nx XName
s
Doc -> Doc -> Doc
$$ String -> Doc
text String
"-- No instances required: synonym is isomorphic to the original."
ppHighLevelDecl NameConverter
nx (RestrictSimpleType XName
t XName
s [Restrict]
r Comment
comm) =
CommentPosition -> Comment -> Doc
ppComment CommentPosition
Before Comment
comm
Doc -> Doc -> Doc
$$ String -> Doc
text String
"newtype" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t Doc -> Doc -> Doc
<+> String -> Doc
text String
"="
Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppConId NameConverter
nx XName
s
Doc -> Doc -> Doc
$$ String -> Doc
text String
"instance Eq" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t
Doc -> Doc -> Doc
$$ String -> Doc
text String
"instance Show" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t
Doc -> Doc -> Doc
$$ String -> Doc
text String
"instance Restricts" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppConId NameConverter
nx XName
s
Doc -> Doc -> Doc
$$ String -> Doc
text String
"instance SchemaType" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t
Doc -> Doc -> Doc
$$ String -> Doc
text String
"instance SimpleType" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t
ppHighLevelDecl NameConverter
nx (ExtendSimpleType XName
t XName
s [Attribute]
as Comment
comm) =
CommentPosition -> Comment -> Doc
ppComment CommentPosition
Before Comment
comm
Doc -> Doc -> Doc
$$ String -> Doc
text String
"data" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t
Doc -> Doc -> Doc
$$ String -> Doc
text String
"data" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppConId NameConverter
nx XName
t_attrs
Doc -> Doc -> Doc
$$ String -> Doc
text String
"instance Eq" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t
Doc -> Doc -> Doc
$$ String -> Doc
text String
"instance Eq" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppConId NameConverter
nx XName
t_attrs
Doc -> Doc -> Doc
$$ String -> Doc
text String
"instance Show" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t
Doc -> Doc -> Doc
$$ String -> Doc
text String
"instance Show" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppConId NameConverter
nx XName
t_attrs
Doc -> Doc -> Doc
$$ String -> Doc
text String
"instance SchemaType" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t
Doc -> Doc -> Doc
$$ String -> Doc
text String
"instance Extension" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppConId NameConverter
nx XName
s
where
t_attrs :: XName
t_attrs = let (XName (N String
t_base)) = XName
t in QName -> XName
XName (String -> QName
N (String
t_baseforall a. [a] -> [a] -> [a]
++String
"Attributes"))
ppHighLevelDecl NameConverter
nx (UnionSimpleTypes XName
t [XName]
sts Comment
comm) =
CommentPosition -> Comment -> Doc
ppComment CommentPosition
Before Comment
comm
Doc -> Doc -> Doc
$$ String -> Doc
text String
"data" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t Doc -> Doc -> Doc
<+> String -> Doc
text String
"=" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t
Doc -> Doc -> Doc
$$ String -> Doc
text String
"-- Placeholder for a Union type, not yet implemented."
ppHighLevelDecl NameConverter
nx (EnumSimpleType XName
t [] Comment
comm) =
CommentPosition -> Comment -> Doc
ppComment CommentPosition
Before Comment
comm
Doc -> Doc -> Doc
$$ String -> Doc
text String
"data" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t
ppHighLevelDecl NameConverter
nx (EnumSimpleType XName
t [(XName, Comment)]
is Comment
comm) =
CommentPosition -> Comment -> Doc
ppComment CommentPosition
Before Comment
comm
Doc -> Doc -> Doc
$$ String -> Doc
text String
"data" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t
Doc -> Doc -> Doc
$$ String -> Doc
text String
"instance Eq" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t
Doc -> Doc -> Doc
$$ String -> Doc
text String
"instance Show" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t
Doc -> Doc -> Doc
$$ String -> Doc
text String
"instance Enum" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t
Doc -> Doc -> Doc
$$ String -> Doc
text String
"instance SchemaType" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t
Doc -> Doc -> Doc
$$ String -> Doc
text String
"instance SimpleType" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t
ppHighLevelDecl NameConverter
nx (ElementsAttrs XName
t [Element]
es [Attribute]
as Comment
comm) =
CommentPosition -> Comment -> Doc
ppComment CommentPosition
Before Comment
comm
Doc -> Doc -> Doc
$$ String -> Doc
text String
"data" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t
Doc -> Doc -> Doc
$$ String -> Doc
text String
"instance Eq" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t
Doc -> Doc -> Doc
$$ String -> Doc
text String
"instance Show" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t
Doc -> Doc -> Doc
$$ String -> Doc
text String
"instance SchemaType" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t
ppHighLevelDecl NameConverter
nx (ElementsAttrsAbstract XName
t [(XName, Maybe XName)]
insts Comment
comm) =
CommentPosition -> Comment -> Doc
ppComment CommentPosition
Before Comment
comm
Doc -> Doc -> Doc
$$ String -> Doc
text String
"data" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t
Doc -> Doc -> Doc
$$ String -> Doc
text String
"instance Eq" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t
Doc -> Doc -> Doc
$$ String -> Doc
text String
"instance Show" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t
Doc -> Doc -> Doc
$$ String -> Doc
text String
"instance SchemaType" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t
ppHighLevelDecl NameConverter
nx (ElementOfType e :: Element
e@Element{}) =
CommentPosition -> Comment -> Doc
ppComment CommentPosition
Before (Element -> Comment
elem_comment Element
e)
Doc -> Doc -> Doc
$$ (String -> Doc
text String
"element" Doc -> Doc -> Doc
<> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx (Element -> XName
elem_name Element
e)) Doc -> Doc -> Doc
<+> String -> Doc
text String
"::"
Doc -> Doc -> Doc
<+> String -> Doc
text String
"XMLParser" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppConId NameConverter
nx (Element -> XName
elem_type Element
e)
Doc -> Doc -> Doc
$$ (String -> Doc
text String
"elementToXML" Doc -> Doc -> Doc
<> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx (Element -> XName
elem_name Element
e)) Doc -> Doc -> Doc
<+> String -> Doc
text String
"::"
Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppConId NameConverter
nx (Element -> XName
elem_type Element
e) Doc -> Doc -> Doc
<+> String -> Doc
text String
"-> [Content ()]"
ppHighLevelDecl NameConverter
nx e :: Decl
e@(ElementAbstractOfType XName
n XName
t [(XName, Maybe XName)]
substgrp Comment
comm)
| forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any forall {a} {a}. (a, Maybe a) -> Bool
notInScope [(XName, Maybe XName)]
substgrp
= (String -> Doc
text String
"element" Doc -> Doc -> Doc
<> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
n) Doc -> Doc -> Doc
<+> String -> Doc
text String
"::"
Doc -> Doc -> Doc
<+> String -> Doc
text String
"XMLParser" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppConId NameConverter
nx XName
t
Doc -> Doc -> Doc
$$ (String -> Doc
text String
"elementToXML" Doc -> Doc -> Doc
<> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
n) Doc -> Doc -> Doc
<+> String -> Doc
text String
"::"
Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppConId NameConverter
nx XName
t Doc -> Doc -> Doc
<+> String -> Doc
text String
"-> [Content ()]"
| Bool
otherwise = NameConverter -> Decl -> Doc
ppElementAbstractOfType NameConverter
nx Decl
e
where
notInScope :: (a, Maybe a) -> Bool
notInScope (a
_,Just a
_) = Bool
True
notInScope (a
_,Maybe a
Nothing) = Bool
False
ppHighLevelDecl NameConverter
nx (Choice XName
t [Element]
es Comment
comm) =
CommentPosition -> Comment -> Doc
ppComment CommentPosition
Before Comment
comm
Doc -> Doc -> Doc
$$ String -> Doc
text String
"data" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t
Doc -> Doc -> Doc
$$ String -> Doc
text String
"instance Eq" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t
Doc -> Doc -> Doc
$$ String -> Doc
text String
"instance Show" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t
ppHighLevelDecl NameConverter
nx (Group XName
t [Element]
es Comment
comm) = Doc
PP.empty
ppHighLevelDecl NameConverter
nx (RestrictComplexType XName
t XName
s Comment
comm) =
CommentPosition -> Comment -> Doc
ppComment CommentPosition
Before Comment
comm
Doc -> Doc -> Doc
$$ String -> Doc
text String
"newtype" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t Doc -> Doc -> Doc
<+> String -> Doc
text String
"="
Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppConId NameConverter
nx XName
s
Doc -> Doc -> Doc
$$ String -> Doc
text String
"-- plus different (more restrictive) parser"
Doc -> Doc -> Doc
$$ String -> Doc
text String
"instance Eq" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t
Doc -> Doc -> Doc
$$ String -> Doc
text String
"instance Show" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t
Doc -> Doc -> Doc
$$ String -> Doc
text String
"instance Restricts" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppConId NameConverter
nx XName
s
Doc -> Doc -> Doc
$$ String -> Doc
text String
"instance SchemaType" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t
ppHighLevelDecl NameConverter
nx (ExtendComplexType XName
t XName
s [Element]
oes [Attribute]
oas [Element]
es [Attribute]
as
Maybe XName
fwdReqd Bool
absSup [XName]
grandsuper Comment
comm) =
NameConverter -> Decl -> Doc
ppHighLevelDecl NameConverter
nx (XName -> [Element] -> [Attribute] -> Comment -> Decl
ElementsAttrs XName
t ([Element]
oesforall a. [a] -> [a] -> [a]
++[Element]
es) ([Attribute]
oasforall a. [a] -> [a] -> [a]
++[Attribute]
as) Comment
comm)
Doc -> Doc -> Doc
$$ NameConverter
-> XName
-> XName
-> Maybe XName
-> Bool
-> [Element]
-> [Attribute]
-> [Element]
-> [Attribute]
-> Doc
ppExtension NameConverter
nx XName
t XName
s Maybe XName
fwdReqd Bool
absSup [Element]
oes [Attribute]
oas [Element]
es [Attribute]
as
Doc -> Doc -> Doc
$$ (if Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [XName]
grandsuper)
then NameConverter -> XName -> [XName] -> (XName, Maybe XName) -> Doc
ppSuperExtension NameConverter
nx XName
s [XName]
grandsuper (XName
t,forall a. Maybe a
Nothing)
else Doc
empty)
ppHighLevelDecl NameConverter
nx (ExtendComplexTypeAbstract XName
t XName
s [(XName, Maybe XName)]
insts
Maybe XName
fwdReqd [XName]
grandsuper Comment
comm) =
NameConverter -> Decl -> Doc
ppHighLevelDecl NameConverter
nx (XName -> [(XName, Maybe XName)] -> Comment -> Decl
ElementsAttrsAbstract XName
t [(XName, Maybe XName)]
insts Comment
comm)
Doc -> Doc -> Doc
$$ NameConverter
-> XName
-> XName
-> Maybe XName
-> Bool
-> [Element]
-> [Attribute]
-> [Element]
-> [Attribute]
-> Doc
ppExtension NameConverter
nx XName
t XName
s Maybe XName
fwdReqd Bool
True [] [] [] []
ppHighLevelDecl NameConverter
nx (XSDInclude XName
m Comment
comm) =
CommentPosition -> Comment -> Doc
ppComment CommentPosition
After Comment
comm
Doc -> Doc -> Doc
$$ String -> Doc
text String
"import {-# SOURCE #-}" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppModId NameConverter
nx XName
m
ppHighLevelDecl NameConverter
nx (XSDImport XName
m Maybe XName
ma Comment
comm) =
CommentPosition -> Comment -> Doc
ppComment CommentPosition
After Comment
comm
Doc -> Doc -> Doc
$$ String -> Doc
text String
"import {-# SOURCE #-}" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppModId NameConverter
nx XName
m
Doc -> Doc -> Doc
<+> forall b a. b -> (a -> b) -> Maybe a -> b
maybe Doc
empty (\XName
a->String -> Doc
text String
"as"Doc -> Doc -> Doc
<+>NameConverter -> XName -> Doc
ppConId NameConverter
nx XName
a) Maybe XName
ma
ppHighLevelDecl NameConverter
nx (XSDComment Comment
comm) =
CommentPosition -> Comment -> Doc
ppComment CommentPosition
Before Comment
comm
ppHighLevelInstances :: NameConverter -> Decl -> Doc
ppHighLevelInstances :: NameConverter -> Decl -> Doc
ppHighLevelInstances NameConverter
nx (ElementsAttrsAbstract XName
t [(XName, Maybe XName)]
insts Comment
comm) =
String -> Doc
text String
"instance SchemaType" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t
ppHighLevelInstances NameConverter
nx e :: Decl
e@(ElementAbstractOfType XName
n XName
t [(XName, Maybe XName)]
substgrp Comment
comm)
| forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any forall {a} {a}. (a, Maybe a) -> Bool
notInScope [(XName, Maybe XName)]
substgrp = NameConverter -> Decl -> Doc
ppElementAbstractOfType NameConverter
nx Decl
e
| Bool
otherwise = Doc
empty
where
notInScope :: (a, Maybe a) -> Bool
notInScope (a
_,Just a
_) = Bool
True
notInScope (a
_,Maybe a
Nothing) = Bool
False
ppHighLevelInstances NameConverter
nx (ExtendComplexType XName
t XName
s [Element]
oes [Attribute]
oas [Element]
es [Attribute]
as
Maybe XName
fwdReqd Bool
absSup [XName]
grandsuper Comment
comm) =
Doc
empty
ppHighLevelInstances NameConverter
nx (ExtendComplexTypeAbstract XName
t XName
s [(XName, Maybe XName)]
insts
Maybe XName
fwdReqd [XName]
grandsuper Comment
comm) =
NameConverter -> Decl -> Doc
ppHighLevelInstances NameConverter
nx (XName -> [(XName, Maybe XName)] -> Comment -> Decl
ElementsAttrsAbstract XName
t [(XName, Maybe XName)]
insts Comment
comm)
ppElementAbstractOfType :: NameConverter -> Decl -> Doc
ppElementAbstractOfType NameConverter
nx (ElementAbstractOfType XName
n XName
t [(XName, Maybe XName)]
substgrp Comment
comm) =
CommentPosition -> Comment -> Doc
ppComment CommentPosition
Before Comment
comm
Doc -> Doc -> Doc
$$ (String -> Doc
text String
"element" Doc -> Doc -> Doc
<> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
n) Doc -> Doc -> Doc
<+> String -> Doc
text String
"::"
Doc -> Doc -> Doc
<+> String -> Doc
text String
"XMLParser" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppConId NameConverter
nx XName
t
ppExtension :: NameConverter -> XName -> XName -> Maybe XName -> Bool ->
[Element] -> [Attribute] -> [Element] -> [Attribute] -> Doc
ppExtension :: NameConverter
-> XName
-> XName
-> Maybe XName
-> Bool
-> [Element]
-> [Attribute]
-> [Element]
-> [Attribute]
-> Doc
ppExtension NameConverter
nx XName
t XName
s Maybe XName
fwdReqd Bool
abstractSuper [Element]
oes [Attribute]
oas [Element]
es [Attribute]
as =
String -> Doc
text String
"instance Extension" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppConId NameConverter
nx XName
s
ppSuperExtension :: NameConverter -> XName -> [XName]
-> (XName,Maybe XName) -> Doc
ppSuperExtension :: NameConverter -> XName -> [XName] -> (XName, Maybe XName) -> Doc
ppSuperExtension NameConverter
nx XName
super (XName
grandSuper:[XName]
_) (XName
t,Just XName
mod) =
String -> Doc
text String
"-- instance Extension" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppConId NameConverter
nx XName
grandSuper
Doc -> Doc -> Doc
$$ String -> Doc
text String
"-- will be declared in module" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppModId NameConverter
nx XName
mod
ppSuperExtension NameConverter
nx XName
super [XName]
grandSupers (XName
t,Maybe XName
Nothing) =
[Doc] -> Doc
vcat (forall a b. (a -> b) -> [a] -> [b]
map (XName -> [XName] -> Doc
ppSuper XName
t forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [a]
reverse) (forall a. Int -> [a] -> [a]
drop Int
2 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [[a]]
inits forall a b. (a -> b) -> a -> b
$ XName
superforall a. a -> [a] -> [a]
: [XName]
grandSupers))
where
ppSuper :: XName -> [XName] -> Doc
ppSuper :: XName -> [XName] -> Doc
ppSuper XName
t gss :: [XName]
gss@(XName
gs:[XName]
_) =
String -> Doc
text String
"instance Extension" Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppUnqConId NameConverter
nx XName
t Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppConId NameConverter
nx XName
gs
ppFields :: NameConverter -> XName -> [Element] -> [Attribute] -> Doc
ppFields :: NameConverter -> XName -> [Element] -> [Attribute] -> Doc
ppFields NameConverter
nx XName
t [Element]
es [Attribute]
as | forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Element]
es Bool -> Bool -> Bool
&& forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Attribute]
as = Doc
empty
ppFields NameConverter
nx XName
t [Element]
es [Attribute]
as = forall a. String -> String -> String -> (a -> Doc) -> [a] -> Doc
ppvList String
"{" String
"," String
"}" forall a. a -> a
id [Doc]
fields
where
fields :: [Doc]
fields = forall a b. (a -> b) -> [a] -> [b]
map (NameConverter -> XName -> Attribute -> Doc
ppFieldAttribute NameConverter
nx XName
t) [Attribute]
as forall a. [a] -> [a] -> [a]
++
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (NameConverter -> XName -> Element -> Int -> Doc
ppFieldElement NameConverter
nx XName
t) [Element]
es [Int
0..]
ppFieldElement :: NameConverter -> XName -> Element -> Int -> Doc
ppFieldElement :: NameConverter -> XName -> Element -> Int -> Doc
ppFieldElement NameConverter
nx XName
t e :: Element
e@Element{} Int
_ = NameConverter -> XName -> XName -> Doc
ppFieldId NameConverter
nx XName
t (Element -> XName
elem_name Element
e)
Doc -> Doc -> Doc
<+> String -> Doc
text String
"::" Doc -> Doc -> Doc
<+> NameConverter -> (Doc -> Doc) -> Element -> Doc
ppElemTypeName NameConverter
nx forall a. a -> a
id Element
e
Doc -> Doc -> Doc
$$ CommentPosition -> Comment -> Doc
ppComment CommentPosition
After (Element -> Comment
elem_comment Element
e)
ppFieldElement NameConverter
nx XName
t e :: Element
e@OneOf{} Int
i = NameConverter -> XName -> XName -> Doc
ppFieldId NameConverter
nx XName
t (QName -> XName
XName forall a b. (a -> b) -> a -> b
$ String -> QName
N forall a b. (a -> b) -> a -> b
$ String
"choice"forall a. [a] -> [a] -> [a]
++forall a. Show a => a -> String
show Int
i)
Doc -> Doc -> Doc
<+> String -> Doc
text String
"::" Doc -> Doc -> Doc
<+> NameConverter -> (Doc -> Doc) -> Element -> Doc
ppElemTypeName NameConverter
nx forall a. a -> a
id Element
e
Doc -> Doc -> Doc
$$ CommentPosition -> Comment -> Doc
ppComment CommentPosition
After (Element -> Comment
elem_comment Element
e)
ppFieldElement NameConverter
nx XName
t e :: Element
e@AnyElem{} Int
i = NameConverter -> XName -> XName -> Doc
ppFieldId NameConverter
nx XName
t (QName -> XName
XName forall a b. (a -> b) -> a -> b
$ String -> QName
N forall a b. (a -> b) -> a -> b
$ String
"any"forall a. [a] -> [a] -> [a]
++forall a. Show a => a -> String
show Int
i)
Doc -> Doc -> Doc
<+> String -> Doc
text String
"::" Doc -> Doc -> Doc
<+> NameConverter -> (Doc -> Doc) -> Element -> Doc
ppElemTypeName NameConverter
nx forall a. a -> a
id Element
e
Doc -> Doc -> Doc
$$ CommentPosition -> Comment -> Doc
ppComment CommentPosition
After (Element -> Comment
elem_comment Element
e)
ppFieldElement NameConverter
nx XName
t e :: Element
e@Text{} Int
i = NameConverter -> XName -> XName -> Doc
ppFieldId NameConverter
nx XName
t (QName -> XName
XName forall a b. (a -> b) -> a -> b
$ String -> QName
N forall a b. (a -> b) -> a -> b
$ String
"text"forall a. [a] -> [a] -> [a]
++forall a. Show a => a -> String
show Int
i)
Doc -> Doc -> Doc
<+> String -> Doc
text String
"::" Doc -> Doc -> Doc
<+> NameConverter -> (Doc -> Doc) -> Element -> Doc
ppElemTypeName NameConverter
nx forall a. a -> a
id Element
e
ppElemTypeName :: NameConverter -> (Doc->Doc) -> Element -> Doc
ppElemTypeName :: NameConverter -> (Doc -> Doc) -> Element -> Doc
ppElemTypeName NameConverter
nx Doc -> Doc
brack e :: Element
e@Element{} =
Modifier -> (Doc -> Doc) -> Doc -> Doc
ppTypeModifier (Element -> Modifier
elem_modifier Element
e) Doc -> Doc
brack forall a b. (a -> b) -> a -> b
$ NameConverter -> XName -> Doc
ppConId NameConverter
nx (Element -> XName
elem_type Element
e)
ppElemTypeName NameConverter
nx Doc -> Doc
brack e :: Element
e@OneOf{} =
Doc -> Doc
brack forall a b. (a -> b) -> a -> b
$ Modifier -> (Doc -> Doc) -> Doc -> Doc
ppTypeModifier (Element -> Modifier
elem_modifier Element
e) Doc -> Doc
parens forall a b. (a -> b) -> a -> b
$
String -> Doc
text String
"OneOf" Doc -> Doc -> Doc
<> String -> Doc
text (forall a. Show a => a -> String
show (forall (t :: * -> *) a. Foldable t => t a -> Int
length (Element -> [[Element]]
elem_oneOf Element
e)))
Doc -> Doc -> Doc
<+> [Doc] -> Doc
hsep (forall a b. (a -> b) -> [a] -> [b]
map [Element] -> Doc
ppSeq (Element -> [[Element]]
elem_oneOf Element
e))
where
ppSeq :: [Element] -> Doc
ppSeq [] = String -> Doc
text String
"()"
ppSeq [Element
e] = NameConverter -> (Doc -> Doc) -> Element -> Doc
ppElemTypeName NameConverter
nx Doc -> Doc
parens Element
e
ppSeq [Element]
es = String -> Doc
text String
"(" Doc -> Doc -> Doc
<> [Doc] -> Doc
hcat (forall a. a -> [a] -> [a]
intersperse (String -> Doc
text String
",")
(forall a b. (a -> b) -> [a] -> [b]
map (NameConverter -> (Doc -> Doc) -> Element -> Doc
ppElemTypeName NameConverter
nx Doc -> Doc
parens) [Element]
es))
Doc -> Doc -> Doc
<> String -> Doc
text String
")"
ppElemTypeName NameConverter
nx Doc -> Doc
brack e :: Element
e@AnyElem{} =
Doc -> Doc
brack forall a b. (a -> b) -> a -> b
$ Modifier -> (Doc -> Doc) -> Doc -> Doc
ppTypeModifier (Element -> Modifier
elem_modifier Element
e) forall a. a -> a
id forall a b. (a -> b) -> a -> b
$
String -> Doc
text String
"AnyElement"
ppElemTypeName NameConverter
nx Doc -> Doc
brack e :: Element
e@Text{} =
String -> Doc
text String
"String"
ppFieldAttribute :: NameConverter -> XName -> Attribute -> Doc
ppFieldAttribute :: NameConverter -> XName -> Attribute -> Doc
ppFieldAttribute NameConverter
nx XName
t Attribute
a = NameConverter -> XName -> XName -> Doc
ppFieldId NameConverter
nx XName
t (Attribute -> XName
attr_name Attribute
a) Doc -> Doc -> Doc
<+> String -> Doc
text String
"::"
Doc -> Doc -> Doc
<+> NameConverter -> XName -> Doc
ppConId NameConverter
nx (Attribute -> XName
attr_type Attribute
a)
Doc -> Doc -> Doc
$$ CommentPosition -> Comment -> Doc
ppComment CommentPosition
After (Attribute -> Comment
attr_comment Attribute
a)
ppTypeModifier :: Modifier -> (Doc->Doc) -> Doc -> Doc
ppTypeModifier :: Modifier -> (Doc -> Doc) -> Doc -> Doc
ppTypeModifier Modifier
Single Doc -> Doc
_ Doc
d = Doc
d
ppTypeModifier Modifier
Optional Doc -> Doc
k Doc
d = Doc -> Doc
k forall a b. (a -> b) -> a -> b
$ String -> Doc
text String
"Maybe" Doc -> Doc -> Doc
<+> Doc -> Doc
k Doc
d
ppTypeModifier (Range (Occurs Maybe Int
Nothing Maybe Int
Nothing)) Doc -> Doc
_ Doc
d = Doc
d
ppTypeModifier (Range (Occurs (Just Int
0) Maybe Int
Nothing)) Doc -> Doc
k Doc
d = Doc -> Doc
k forall a b. (a -> b) -> a -> b
$ String -> Doc
text String
"Maybe" Doc -> Doc -> Doc
<+> Doc -> Doc
k Doc
d
ppTypeModifier (Range (Occurs Maybe Int
_ Maybe Int
_)) Doc -> Doc
_ Doc
d = String -> Doc
text String
"[" Doc -> Doc -> Doc
<> Doc
d Doc -> Doc -> Doc
<> String -> Doc
text String
"]"
ppElemModifier :: Modifier -> Doc -> Doc
ppElemModifier Modifier
Single Doc
doc = Doc
doc
ppElemModifier Modifier
Optional Doc
doc = String -> Doc
text String
"optional" Doc -> Doc -> Doc
<+> Doc -> Doc
parens Doc
doc
ppElemModifier (Range (Occurs Maybe Int
Nothing Maybe Int
Nothing)) Doc
doc = Doc
doc
ppElemModifier (Range (Occurs (Just Int
0) Maybe Int
Nothing)) Doc
doc = String -> Doc
text String
"optional"
Doc -> Doc -> Doc
<+> Doc -> Doc
parens Doc
doc
ppElemModifier (Range Occurs
o) Doc
doc = String -> Doc
text String
"between" Doc -> Doc -> Doc
<+> (Doc -> Doc
parens (String -> Doc
text (forall a. Show a => a -> String
show Occurs
o))
Doc -> Doc -> Doc
$$ Doc -> Doc
parens Doc
doc)
paragraph :: Int -> String -> String
paragraph :: Int -> String -> String
paragraph Int
n String
s = Int -> [String] -> String
go Int
n (String -> [String]
words String
s)
where go :: Int -> [String] -> String
go Int
i [] = []
go Int
i (String
x:[String]
xs) | Int
lenforall a. Ord a => a -> a -> Bool
<Int
i = String
xforall a. [a] -> [a] -> [a]
++String
" "forall a. [a] -> [a] -> [a]
++Int -> [String] -> String
go (Int
iforall a. Num a => a -> a -> a
-Int
lenforall a. Num a => a -> a -> a
-Int
1) [String]
xs
| Bool
otherwise = String
"\n"forall a. [a] -> [a] -> [a]
++String
xforall a. [a] -> [a] -> [a]
++String
" "forall a. [a] -> [a] -> [a]
++Int -> [String] -> String
go (Int
nforall a. Num a => a -> a -> a
-Int
lenforall a. Num a => a -> a -> a
-Int
1) [String]
xs
where len :: Int
len = forall (t :: * -> *) a. Foldable t => t a -> Int
length String
x
uniqueify :: [Element] -> [Element]
uniqueify :: [Element] -> [Element]
uniqueify = [String] -> [Element] -> [Element]
go []
where
go :: [String] -> [Element] -> [Element]
go [String]
seen [] = []
go [String]
seen (e :: Element
e@Element{}:[Element]
es)
| forall a. Show a => a -> String
show (Element -> XName
elem_name Element
e) forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
seen
= let fresh :: XName
fresh = (String -> Bool) -> XName -> XName
new (forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem`[String]
seen) (Element -> XName
elem_name Element
e) in
Element
e{elem_name :: XName
elem_name=XName
fresh} forall a. a -> [a] -> [a]
: [String] -> [Element] -> [Element]
go (forall a. Show a => a -> String
show XName
freshforall a. a -> [a] -> [a]
:[String]
seen) [Element]
es
| Bool
otherwise = Element
eforall a. a -> [a] -> [a]
: [String] -> [Element] -> [Element]
go (forall a. Show a => a -> String
show (Element -> XName
elem_name Element
e)forall a. a -> [a] -> [a]
: [String]
seen) [Element]
es
go [String]
seen (Element
e:[Element]
es) = Element
e forall a. a -> [a] -> [a]
: [String] -> [Element] -> [Element]
go [String]
seen [Element]
es
new :: (String -> Bool) -> XName -> XName
new String -> Bool
pred (XName (N String
n)) = QName -> XName
XName forall a b. (a -> b) -> a -> b
$ String -> QName
N forall a b. (a -> b) -> a -> b
$ forall a. [a] -> a
head forall a b. (a -> b) -> a -> b
$
forall a. (a -> Bool) -> [a] -> [a]
dropWhile String -> Bool
pred [String
nforall a. [a] -> [a] -> [a]
++forall a. Show a => a -> String
show Integer
i | Integer
i <- [Integer
2..]]
new String -> Bool
pred (XName (QN Namespace
ns String
n)) = QName -> XName
XName forall a b. (a -> b) -> a -> b
$ Namespace -> String -> QName
QN Namespace
ns forall a b. (a -> b) -> a -> b
$ forall a. [a] -> a
head forall a b. (a -> b) -> a -> b
$
forall a. (a -> Bool) -> [a] -> [a]
dropWhile String -> Bool
pred [String
nforall a. [a] -> [a] -> [a]
++forall a. Show a => a -> String
show Integer
i | Integer
i <- [Integer
2..]]