1 {-# LANGUAGE UndecidableInstances #-}
2 module Symantic.XML.Language
3 ( module Symantic.XML.Language
4 , module Symantic.XML.Namespace
5 , module Symantic.XML.Text
6 , module Symantic.Base.Composable
7 , module Symantic.Base.Algebrable
8 , module Symantic.Base.Permutable
11 import Data.Function ((.))
12 import Data.Maybe (Maybe)
13 import Data.Kind (Constraint)
14 import qualified Data.Text.Lazy as TL
16 import Symantic.XML.Namespace
17 import Symantic.XML.Text
18 import Symantic.Base.Algebrable
19 import Symantic.Base.Composable
20 import Symantic.Base.Permutable
29 --xmlPI :: -> repr a k
30 -- | @('namespace' p ns)@ declares a namespace prefix @(p)@
31 -- to be used for the 'Namespace' @(ns)@.
32 -- Or make @(ns)@ the default namespace if @(p)@ is 'Nothing'.
33 namespace :: Maybe NCName -> Namespace -> repr k k
35 Transformable repr => XML (UnTrans repr) =>
36 Maybe NCName -> Namespace -> repr k k
37 namespace n ns = noTrans (namespace n ns)
39 default element :: Transformable repr => XML (UnTrans repr) =>
40 QName -> repr a k -> repr a k
41 element :: QName -> repr a k -> repr a k
42 element n x = noTrans (element n (unTrans x))
44 default attribute :: Transformable repr => XML (UnTrans repr) =>
45 QName -> repr a k -> repr a k
46 attribute :: QName -> repr a k -> repr a k
47 attribute n x = noTrans (attribute n (unTrans x))
49 default pi :: Transformable repr => XML (UnTrans repr) =>
50 PName -> repr (TL.Text -> k) k
51 pi :: PName -> repr (TL.Text -> k) k
54 default literal :: Transformable repr => XML (UnTrans repr) =>
56 literal :: TL.Text -> repr k k
57 literal = noTrans . literal
59 default comment :: Transformable repr => XML (UnTrans repr) =>
61 comment :: repr (TL.Text -> k) k
62 comment = noTrans comment
64 default cdata :: Transformable repr => XML (UnTrans repr) =>
66 cdata :: repr (TL.Text -> k) k
69 -- ** Class 'Textable'
70 class Textable repr where
71 type TextConstraint repr a :: Constraint
72 type TextConstraint repr a = TextConstraint (UnTrans repr) a
73 default text :: Transformable repr => XML (UnTrans repr) =>
74 TextConstraint (UnTrans repr) a => repr (a -> k) k
75 text :: TextConstraint repr a => repr (a -> k) k