blob: fd81bfb52473b32122b9f631eba7dc381697c574 (
plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
|
{-# LANGUAGE NoImplicitPrelude #-}
{- |
Module : Text.Pandoc.Readers.Odt.Generic.Namespaces
Copyright : Copyright (C) 2015 Martin Linnemann
License : GNU GPL, version 2 or above
Maintainer : Martin Linnemann <theCodingMarlin@googlemail.com>
Stability : alpha
Portability : portable
A class containing a set of namespace identifiers. Used to convert between
typesafe Haskell namespace identifiers and unsafe "real world" namespaces.
-}
module Text.Pandoc.Readers.Odt.Generic.Namespaces where
import Prelude
import qualified Data.Map as M
--
type NameSpaceIRI = String
--
type NameSpaceIRIs nsID = M.Map nsID NameSpaceIRI
--
class (Eq nsID, Ord nsID) => NameSpaceID nsID where
-- | Given a IRI, possibly update the map and return the id of the namespace.
-- May fail if the namespace is unknown and the application does not
-- allow unknown namespaces.
getNamespaceID :: NameSpaceIRI
-> NameSpaceIRIs nsID
-> Maybe (NameSpaceIRIs nsID, nsID)
-- | Given a namespace id, lookup its IRI. May be overridden for performance.
getIRI :: nsID
-> NameSpaceIRIs nsID
-> Maybe NameSpaceIRI
-- | The root element of an XML document has a namespace, too, and the
-- "XML.Light-parser" is eager to remove the corresponding namespace
-- attribute.
-- As a result, at least this root namespace must be provided.
getInitialIRImap :: NameSpaceIRIs nsID
getIRI = M.lookup
getInitialIRImap = M.empty
|