{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
module Swish.RDF.Graph
(
RDFLabel(..), ToRDFLabel(..), FromRDFLabel(..)
, isLiteral, isUntypedLiteral, isTypedLiteral, isXMLLiteral
, isDatatyped, isMemberProp, isUri, isBlank, isQueryVar
, getLiteralText, getScopedName, makeBlank
, quote
, quoteT
, RDFArcSet
, RDFTriple
, toRDFTriple, fromRDFTriple
, NSGraph(..)
, RDFGraph
, toRDFGraph, emptyRDFGraph
, NamespaceMap
, emptyNamespaceMap
, LookupFormula(..), Formula, FormulaMap, emptyFormulaMap
, addArc, merge
, allLabels, allNodes, remapLabels, remapLabelList
, newNode, newNodes
, setNamespaces, getNamespaces
, setFormulae, getFormulae, setFormula, getFormula
, fmapNSGraph
, traverseNSGraph
, LDGraph(..), Label (..), Arc(..)
, arc, Selector
, resRdfRDF
, resRdfDescription
, resRdfID
, resRdfAbout
, resRdfParseType
, resRdfResource
, resRdfLi
, resRdfNodeID
, resRdfDatatype
, resRdf1, resRdf2, resRdfn
, resRdfsResource
, resRdfsClass
, resRdfsLiteral
, resRdfsDatatype
, resRdfXMLLiteral
, resRdfProperty
, resRdfsRange
, resRdfsDomain
, resRdfType
, resRdfsSubClassOf
, resRdfsSubPropertyOf
, resRdfsLabel
, resRdfsComment
, resRdfsContainer
, resRdfBag
, resRdfSeq
, resRdfAlt
, resRdfsContainerMembershipProperty
, resRdfsMember
, resRdfList
, resRdfFirst
, resRdfRest
, resRdfNil
, resRdfStatement
, resRdfSubject
, resRdfPredicate
, resRdfObject
, resRdfsSeeAlso
, resRdfsIsDefinedBy
, resRdfValue
, resOwlSameAs
, resRdfdGeneralRestriction
, resRdfdOnProperties, resRdfdConstraint, resRdfdMaxCardinality
, resLogImplies
, grMatchMap, grEq
, mapnode, maplist
)
where
import qualified Data.Map as M
import qualified Data.Set as S
import qualified Data.Text as T
import qualified Data.Text.Read as T
import qualified Data.Traversable as Traversable
#if (!defined(__GLASGOW_HASKELL__)) || (__GLASGOW_HASKELL__ < 710)
import Control.Applicative (Applicative(pure), (<$>), (<*>))
import Data.Monoid (Monoid(..))
#endif
import Control.Arrow ((***))
import Data.Char (ord, isDigit)
import Data.Foldable (Foldable(..))
import Data.Hashable (hashWithSalt)
import Data.List (intersect, union)
import Data.Maybe (mapMaybe)
import Data.Word (Word32)
import Data.String (IsString(..))
#if MIN_VERSION_time(1,5,0)
import Data.Time (UTCTime, Day, ParseTime, parseTimeM, formatTime, defaultTimeLocale)
#else
import Data.Time (UTCTime, Day, ParseTime, parseTime, formatTime)
import System.Locale (defaultTimeLocale)
#endif
#if !(MIN_VERSION_base(4, 11, 0))
import Data.Semigroup
#endif
import Network.URI (URI)
import Text.Printf
import Prelude hiding (Foldable(..))
import Swish.Namespace
( getNamespaceTuple
, getScopedNameURI
, ScopedName
, getScopeLocal, getScopeNamespace
, getQName
, makeQNameScopedName
, makeURIScopedName
, nullScopedName
)
import Swish.RDF.Vocabulary (LanguageTag)
import Swish.RDF.Vocabulary (fromLangTag, xsdBoolean, xsdDate, xsdDateTime, xsdDecimal, xsdDouble, xsdFloat, xsdInteger
, rdfType, rdfList, rdfFirst, rdfRest, rdfNil
, rdfsMember, rdfdGeneralRestriction, rdfdOnProperties, rdfdConstraint, rdfdMaxCardinality
, rdfsSeeAlso, rdfValue, rdfsLabel, rdfsComment, rdfProperty
, rdfsSubPropertyOf, rdfsSubClassOf, rdfsClass, rdfsLiteral
, rdfsDatatype, rdfXMLLiteral, rdfsRange, rdfsDomain, rdfsContainer
, rdfBag, rdfSeq, rdfAlt
, rdfsContainerMembershipProperty, rdfsIsDefinedBy
, rdfsResource, rdfStatement, rdfSubject, rdfPredicate, rdfObject
, rdfRDF, rdfDescription, rdfID, rdfAbout, rdfParseType
, rdfResource, rdfLi, rdfNodeID, rdfDatatype, rdfXMLLiteral
, rdf1, rdf2, rdfn
, owlSameAs, logImplies, namespaceRDF
)
import Swish.GraphClass (LDGraph(..), Label (..), Arc(..), ArcSet, Selector)
import Swish.GraphClass (arc, arcLabels, getComponents)
import Swish.GraphMatch (LabelMap, ScopedLabel(..))
import Swish.GraphMatch (graphMatch)
import Swish.QName (QName, getLName)
data RDFLabel =
Res ScopedName
| Lit T.Text
| LangLit T.Text LanguageTag
| TypedLit T.Text ScopedName
| Blank String
| Var String
| NoNode
instance Eq RDFLabel where
Res ScopedName
q1 == :: RDFLabel -> RDFLabel -> Bool
== Res ScopedName
q2 = ScopedName
q1 ScopedName -> ScopedName -> Bool
forall a. Eq a => a -> a -> Bool
== ScopedName
q2
Blank [Char]
b1 == Blank [Char]
b2 = [Char]
b1 [Char] -> [Char] -> Bool
forall a. Eq a => a -> a -> Bool
== [Char]
b2
Var [Char]
v1 == Var [Char]
v2 = [Char]
v1 [Char] -> [Char] -> Bool
forall a. Eq a => a -> a -> Bool
== [Char]
v2
Lit Text
s1 == Lit Text
s2 = Text
s1 Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
s2
LangLit Text
s1 LanguageTag
l1 == LangLit Text
s2 LanguageTag
l2 = Text
s1 Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
s2 Bool -> Bool -> Bool
&& LanguageTag
l1 LanguageTag -> LanguageTag -> Bool
forall a. Eq a => a -> a -> Bool
== LanguageTag
l2
TypedLit Text
s1 ScopedName
t1 == TypedLit Text
s2 ScopedName
t2 = Text
s1 Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
s2 Bool -> Bool -> Bool
&& ScopedName
t1 ScopedName -> ScopedName -> Bool
forall a. Eq a => a -> a -> Bool
== ScopedName
t2
RDFLabel
_ == RDFLabel
_ = Bool
False
instance Show RDFLabel where
show :: RDFLabel -> [Char]
show (Res ScopedName
sn) = ScopedName -> [Char]
forall a. Show a => a -> [Char]
show ScopedName
sn
show (Lit Text
st) = Text -> [Char]
quote1Str Text
st
show (LangLit Text
st LanguageTag
lang) = Text -> [Char]
quote1Str Text
st [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char]
"@" [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> [Char]
T.unpack (LanguageTag -> Text
fromLangTag LanguageTag
lang)
show (TypedLit Text
st ScopedName
dtype)
| ScopedName
dtype ScopedName -> [ScopedName] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [ScopedName
xsdBoolean, ScopedName
xsdDouble, ScopedName
xsdDecimal, ScopedName
xsdInteger] = Text -> [Char]
T.unpack Text
st
| Bool
otherwise = Text -> [Char]
quote1Str Text
st [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char]
"^^" [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ ScopedName -> [Char]
forall a. Show a => a -> [Char]
show ScopedName
dtype
show (Blank [Char]
ln) = [Char]
"_:" [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char]
ln
show (Var [Char]
ln) = Char
'?' Char -> ShowS
forall a. a -> [a] -> [a]
: [Char]
ln
show RDFLabel
NoNode = [Char]
"<NoNode>"
instance Ord RDFLabel where
compare :: RDFLabel -> RDFLabel -> Ordering
compare (Res ScopedName
sn1) (Res ScopedName
sn2) = ScopedName -> ScopedName -> Ordering
forall a. Ord a => a -> a -> Ordering
compare ScopedName
sn1 ScopedName
sn2
compare (Res ScopedName
_) RDFLabel
_ = Ordering
LT
compare RDFLabel
_ (Res ScopedName
_) = Ordering
GT
compare (Lit Text
s1) (Lit Text
s2) = Text -> Text -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Text
s1 Text
s2
compare (Lit Text
_) RDFLabel
_ = Ordering
LT
compare RDFLabel
_ (Lit Text
_) = Ordering
GT
compare (LangLit Text
s1 LanguageTag
l1) (LangLit Text
s2 LanguageTag
l2) = (Text, LanguageTag) -> (Text, LanguageTag) -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Text
s1,LanguageTag
l1) (Text
s2,LanguageTag
l2)
compare (LangLit Text
_ LanguageTag
_) RDFLabel
_ = Ordering
LT
compare RDFLabel
_ (LangLit Text
_ LanguageTag
_) = Ordering
GT
compare (TypedLit Text
s1 ScopedName
t1) (TypedLit Text
s2 ScopedName
t2) = (Text, ScopedName) -> (Text, ScopedName) -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Text
s1,ScopedName
t1) (Text
s2,ScopedName
t2)
compare (TypedLit Text
_ ScopedName
_) RDFLabel
_ = Ordering
LT
compare RDFLabel
_ (TypedLit Text
_ ScopedName
_) = Ordering
GT
compare (Blank [Char]
ln1) (Blank [Char]
ln2) = [Char] -> [Char] -> Ordering
forall a. Ord a => a -> a -> Ordering
compare [Char]
ln1 [Char]
ln2
compare (Blank [Char]
_) RDFLabel
_ = Ordering
LT
compare RDFLabel
_ (Blank [Char]
_) = Ordering
GT
compare (Var [Char]
ln1) (Var [Char]
ln2) = [Char] -> [Char] -> Ordering
forall a. Ord a => a -> a -> Ordering
compare [Char]
ln1 [Char]
ln2
compare (Var [Char]
_) RDFLabel
NoNode = Ordering
LT
compare RDFLabel
_ (Var [Char]
_) = Ordering
GT
compare RDFLabel
NoNode RDFLabel
NoNode = Ordering
EQ
instance Label RDFLabel where
labelIsVar :: RDFLabel -> Bool
labelIsVar (Blank [Char]
_) = Bool
True
labelIsVar (Var [Char]
_) = Bool
True
labelIsVar RDFLabel
_ = Bool
False
getLocal :: RDFLabel -> [Char]
getLocal (Blank [Char]
loc) = [Char]
loc
getLocal (Var [Char]
loc) = Char
'?'Char -> ShowS
forall a. a -> [a] -> [a]
:[Char]
loc
getLocal (Res ScopedName
sn) = [Char]
"Res_" [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ (Text -> [Char]
T.unpack (Text -> [Char]) -> (ScopedName -> Text) -> ScopedName -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LName -> Text
getLName (LName -> Text) -> (ScopedName -> LName) -> ScopedName -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ScopedName -> LName
getScopeLocal) ScopedName
sn
getLocal RDFLabel
NoNode = [Char]
"None"
getLocal RDFLabel
_ = [Char]
"Lit_"
makeLabel :: [Char] -> RDFLabel
makeLabel (Char
'?':[Char]
loc) = [Char] -> RDFLabel
Var [Char]
loc
makeLabel [Char]
loc = [Char] -> RDFLabel
Blank [Char]
loc
labelHash :: Int -> RDFLabel -> Int
labelHash Int
seed RDFLabel
lb = Int -> [Char] -> Int
forall a. Hashable a => Int -> a -> Int
hashWithSalt Int
seed (RDFLabel -> [Char]
showCanon RDFLabel
lb)
instance IsString RDFLabel where
fromString :: [Char] -> RDFLabel
fromString = Text -> RDFLabel
Lit (Text -> RDFLabel) -> ([Char] -> Text) -> [Char] -> RDFLabel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Text
T.pack
class ToRDFLabel a where
toRDFLabel :: a -> RDFLabel
class FromRDFLabel a where
fromRDFLabel :: RDFLabel -> Maybe a
instance ToRDFLabel RDFLabel where
toRDFLabel :: RDFLabel -> RDFLabel
toRDFLabel = RDFLabel -> RDFLabel
forall a. a -> a
id
instance FromRDFLabel RDFLabel where
fromRDFLabel :: RDFLabel -> Maybe RDFLabel
fromRDFLabel = RDFLabel -> Maybe RDFLabel
forall a. a -> Maybe a
Just
maybeReadStr :: (Read a) => T.Text -> Maybe a
maybeReadStr :: forall a. Read a => Text -> Maybe a
maybeReadStr Text
txt = case ReadS a
forall a. Read a => ReadS a
reads (Text -> [Char]
T.unpack Text
txt) of
[(a
val, [Char]
"")] -> a -> Maybe a
forall a. a -> Maybe a
Just a
val
[(a, [Char])]
_ -> Maybe a
forall a. Maybe a
Nothing
maybeRead :: T.Reader a -> T.Text -> Maybe a
maybeRead :: forall a. Reader a -> Text -> Maybe a
maybeRead Reader a
rdr Text
inTxt =
case Reader a
rdr Text
inTxt of
Right (a
val, Text
"") -> a -> Maybe a
forall a. a -> Maybe a
Just a
val
Either [Char] (a, Text)
_ -> Maybe a
forall a. Maybe a
Nothing
fLabel :: (T.Text -> Maybe a) -> ScopedName -> RDFLabel -> Maybe a
fLabel :: forall a. (Text -> Maybe a) -> ScopedName -> RDFLabel -> Maybe a
fLabel Text -> Maybe a
conv ScopedName
dtype (TypedLit Text
xs ScopedName
dt) | ScopedName
dt ScopedName -> ScopedName -> Bool
forall a. Eq a => a -> a -> Bool
== ScopedName
dtype = Text -> Maybe a
conv Text
xs
| Bool
otherwise = Maybe a
forall a. Maybe a
Nothing
fLabel Text -> Maybe a
_ ScopedName
_ RDFLabel
_ = Maybe a
forall a. Maybe a
Nothing
tLabel :: (Show a) => ScopedName -> (String -> T.Text) -> a -> RDFLabel
tLabel :: forall a. Show a => ScopedName -> ([Char] -> Text) -> a -> RDFLabel
tLabel ScopedName
dtype [Char] -> Text
conv = (Text -> ScopedName -> RDFLabel) -> ScopedName -> Text -> RDFLabel
forall a b c. (a -> b -> c) -> b -> a -> c
flip Text -> ScopedName -> RDFLabel
TypedLit ScopedName
dtype (Text -> RDFLabel) -> (a -> Text) -> a -> RDFLabel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Text
conv ([Char] -> Text) -> (a -> [Char]) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> [Char]
forall a. Show a => a -> [Char]
show
instance ToRDFLabel Char where
toRDFLabel :: Char -> RDFLabel
toRDFLabel = Text -> RDFLabel
Lit (Text -> RDFLabel) -> (Char -> Text) -> Char -> RDFLabel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Text
T.singleton
instance FromRDFLabel Char where
fromRDFLabel :: RDFLabel -> Maybe Char
fromRDFLabel (Lit Text
cs) | Text -> Int -> Ordering
T.compareLength Text
cs Int
1 Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
EQ = Char -> Maybe Char
forall a. a -> Maybe a
Just (HasCallStack => Text -> Char
Text -> Char
T.head Text
cs)
| Bool
otherwise = Maybe Char
forall a. Maybe a
Nothing
fromRDFLabel RDFLabel
_ = Maybe Char
forall a. Maybe a
Nothing
instance ToRDFLabel String where
toRDFLabel :: [Char] -> RDFLabel
toRDFLabel = Text -> RDFLabel
Lit (Text -> RDFLabel) -> ([Char] -> Text) -> [Char] -> RDFLabel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Text
T.pack
instance FromRDFLabel String where
fromRDFLabel :: RDFLabel -> Maybe [Char]
fromRDFLabel (Lit Text
xs) = [Char] -> Maybe [Char]
forall a. a -> Maybe a
Just (Text -> [Char]
T.unpack Text
xs)
fromRDFLabel RDFLabel
_ = Maybe [Char]
forall a. Maybe a
Nothing
textToBool :: T.Text -> Maybe Bool
textToBool :: Text -> Maybe Bool
textToBool Text
s | Text
s Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text
"1", Text
"true"] = Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True
| Text
s Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text
"0", Text
"false"] = Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
False
| Bool
otherwise = Maybe Bool
forall a. Maybe a
Nothing
instance ToRDFLabel Bool where
toRDFLabel :: Bool -> RDFLabel
toRDFLabel Bool
b = Text -> ScopedName -> RDFLabel
TypedLit (if Bool
b then Text
"true" else Text
"false") ScopedName
xsdBoolean
instance FromRDFLabel Bool where
fromRDFLabel :: RDFLabel -> Maybe Bool
fromRDFLabel = (Text -> Maybe Bool) -> ScopedName -> RDFLabel -> Maybe Bool
forall a. (Text -> Maybe a) -> ScopedName -> RDFLabel -> Maybe a
fLabel Text -> Maybe Bool
textToBool ScopedName
xsdBoolean
fromRealFloat :: (RealFloat a, PrintfArg a) => ScopedName -> a -> RDFLabel
fromRealFloat :: forall a. (RealFloat a, PrintfArg a) => ScopedName -> a -> RDFLabel
fromRealFloat ScopedName
dtype a
f | a -> Bool
forall a. RealFloat a => a -> Bool
isNaN a
f = Text -> RDFLabel
toL Text
"NaN"
| a -> Bool
forall a. RealFloat a => a -> Bool
isInfinite a
f = Text -> RDFLabel
toL (Text -> RDFLabel) -> Text -> RDFLabel
forall a b. (a -> b) -> a -> b
$ if a
f a -> a -> Bool
forall a. Ord a => a -> a -> Bool
> a
0.0 then Text
"INF" else Text
"-INF"
| Bool
otherwise = Text -> RDFLabel
toL (Text -> RDFLabel) -> Text -> RDFLabel
forall a b. (a -> b) -> a -> b
$ [Char] -> Text
T.pack ([Char] -> Text) -> [Char] -> Text
forall a b. (a -> b) -> a -> b
$ [Char] -> a -> [Char]
forall r. PrintfType r => [Char] -> r
printf [Char]
"%E" a
f
where
toL :: Text -> RDFLabel
toL = (Text -> ScopedName -> RDFLabel) -> ScopedName -> Text -> RDFLabel
forall a b c. (a -> b -> c) -> b -> a -> c
flip Text -> ScopedName -> RDFLabel
TypedLit ScopedName
dtype
textToRealFloat :: (RealFloat a, Read a) => (a -> Maybe a) -> T.Text -> Maybe a
textToRealFloat :: forall a.
(RealFloat a, Read a) =>
(a -> Maybe a) -> Text -> Maybe a
textToRealFloat a -> Maybe a
conv = Text -> Maybe a
rconv
where
rconv :: Text -> Maybe a
rconv Text
"NaN" = a -> Maybe a
forall a. a -> Maybe a
Just (a
0.0 a -> a -> a
forall a. Fractional a => a -> a -> a
/ a
0.0)
rconv Text
"INF" = a -> Maybe a
forall a. a -> Maybe a
Just (a
1.0 a -> a -> a
forall a. Fractional a => a -> a -> a
/ a
0.0)
rconv Text
"-INF" = a -> Maybe a
forall a. a -> Maybe a
Just ((-a
1.0) a -> a -> a
forall a. Fractional a => a -> a -> a
/ a
0.0)
rconv Text
ival
| Text -> Bool
T.null Text
ival = Maybe a
forall a. Maybe a
Nothing
| Bool
otherwise = case Text -> Maybe a
forall a. Read a => Text -> Maybe a
maybeReadStr Text
ival of
Just a
val -> a -> Maybe a
conv a
val
Maybe a
_ -> if HasCallStack => Text -> Char
Text -> Char
T.last Text
ival Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.'
then Text -> Maybe a
forall a. Read a => Text -> Maybe a
maybeReadStr (Text -> Char -> Text
T.snoc Text
ival Char
'0') Maybe a -> (a -> Maybe a) -> Maybe a
forall a b. Maybe a -> (a -> Maybe b) -> Maybe b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= a -> Maybe a
conv
else Maybe a
forall a. Maybe a
Nothing
textToFloat :: T.Text -> Maybe Float
textToFloat :: Text -> Maybe Float
textToFloat =
let
conv :: a -> Maybe a
conv a
f | a -> Bool
forall a. RealFloat a => a -> Bool
isNaN a
f Bool -> Bool -> Bool
|| a -> Bool
forall a. RealFloat a => a -> Bool
isInfinite a
f = Maybe a
forall a. Maybe a
Nothing
| Bool
otherwise = a -> Maybe a
forall a. a -> Maybe a
Just a
f
in (Float -> Maybe Float) -> Text -> Maybe Float
forall a.
(RealFloat a, Read a) =>
(a -> Maybe a) -> Text -> Maybe a
textToRealFloat Float -> Maybe Float
forall {a}. RealFloat a => a -> Maybe a
conv
textToDouble :: T.Text -> Maybe Double
textToDouble :: Text -> Maybe Double
textToDouble = (Double -> Maybe Double) -> Text -> Maybe Double
forall a.
(RealFloat a, Read a) =>
(a -> Maybe a) -> Text -> Maybe a
textToRealFloat Double -> Maybe Double
forall a. a -> Maybe a
Just
instance ToRDFLabel Float where
toRDFLabel :: Float -> RDFLabel
toRDFLabel = ScopedName -> Float -> RDFLabel
forall a. (RealFloat a, PrintfArg a) => ScopedName -> a -> RDFLabel
fromRealFloat ScopedName
xsdFloat
instance FromRDFLabel Float where
fromRDFLabel :: RDFLabel -> Maybe Float
fromRDFLabel = (Text -> Maybe Float) -> ScopedName -> RDFLabel -> Maybe Float
forall a. (Text -> Maybe a) -> ScopedName -> RDFLabel -> Maybe a
fLabel Text -> Maybe Float
textToFloat ScopedName
xsdFloat
instance ToRDFLabel Double where
toRDFLabel :: Double -> RDFLabel
toRDFLabel = ScopedName -> Double -> RDFLabel
forall a. (RealFloat a, PrintfArg a) => ScopedName -> a -> RDFLabel
fromRealFloat ScopedName
xsdDouble
instance FromRDFLabel Double where
fromRDFLabel :: RDFLabel -> Maybe Double
fromRDFLabel = (Text -> Maybe Double) -> ScopedName -> RDFLabel -> Maybe Double
forall a. (Text -> Maybe a) -> ScopedName -> RDFLabel -> Maybe a
fLabel Text -> Maybe Double
textToDouble ScopedName
xsdDouble
instance ToRDFLabel Int where
toRDFLabel :: Int -> RDFLabel
toRDFLabel = ScopedName -> ([Char] -> Text) -> Int -> RDFLabel
forall a. Show a => ScopedName -> ([Char] -> Text) -> a -> RDFLabel
tLabel ScopedName
xsdInteger [Char] -> Text
T.pack
textToInt :: T.Text -> Maybe Int
textToInt :: Text -> Maybe Int
textToInt Text
s =
let conv :: Integer -> Maybe Int
conv :: Integer -> Maybe Int
conv Integer
i =
let lb :: Integer
lb = Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int
forall a. Bounded a => a
minBound :: Int)
ub :: Integer
ub = Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int
forall a. Bounded a => a
maxBound :: Int)
in if (Integer
i Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>= Integer
lb) Bool -> Bool -> Bool
&& (Integer
i Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
ub) then Int -> Maybe Int
forall a. a -> Maybe a
Just (Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
i) else Maybe Int
forall a. Maybe a
Nothing
in Reader Integer -> Text -> Maybe Integer
forall a. Reader a -> Text -> Maybe a
maybeRead (Reader Integer -> Reader Integer
forall a. Num a => Reader a -> Reader a
T.signed Reader Integer
forall a. Integral a => Reader a
T.decimal) Text
s Maybe Integer -> (Integer -> Maybe Int) -> Maybe Int
forall a b. Maybe a -> (a -> Maybe b) -> Maybe b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Integer -> Maybe Int
conv
instance FromRDFLabel Int where
fromRDFLabel :: RDFLabel -> Maybe Int
fromRDFLabel = (Text -> Maybe Int) -> ScopedName -> RDFLabel -> Maybe Int
forall a. (Text -> Maybe a) -> ScopedName -> RDFLabel -> Maybe a
fLabel Text -> Maybe Int
textToInt ScopedName
xsdInteger
instance ToRDFLabel Integer where
toRDFLabel :: Integer -> RDFLabel
toRDFLabel = ScopedName -> ([Char] -> Text) -> Integer -> RDFLabel
forall a. Show a => ScopedName -> ([Char] -> Text) -> a -> RDFLabel
tLabel ScopedName
xsdInteger [Char] -> Text
T.pack
instance FromRDFLabel Integer where
fromRDFLabel :: RDFLabel -> Maybe Integer
fromRDFLabel = (Text -> Maybe Integer) -> ScopedName -> RDFLabel -> Maybe Integer
forall a. (Text -> Maybe a) -> ScopedName -> RDFLabel -> Maybe a
fLabel (Reader Integer -> Text -> Maybe Integer
forall a. Reader a -> Text -> Maybe a
maybeRead (Reader Integer -> Reader Integer
forall a. Num a => Reader a -> Reader a
T.signed Reader Integer
forall a. Integral a => Reader a
T.decimal)) ScopedName
xsdInteger
fromUTCFormat :: UTCTime -> String
fromUTCFormat :: UTCTime -> [Char]
fromUTCFormat = TimeLocale -> [Char] -> UTCTime -> [Char]
forall t. FormatTime t => TimeLocale -> [Char] -> t -> [Char]
formatTime TimeLocale
defaultTimeLocale [Char]
"%FT%T%QZ"
fromDayFormat :: Day -> String
fromDayFormat :: Day -> [Char]
fromDayFormat = TimeLocale -> [Char] -> Day -> [Char]
forall t. FormatTime t => TimeLocale -> [Char] -> t -> [Char]
formatTime TimeLocale
defaultTimeLocale [Char]
"%FZ"
toTimeFormat :: (ParseTime a) => String -> String -> Maybe a
toTimeFormat :: forall a. ParseTime a => [Char] -> [Char] -> Maybe a
toTimeFormat [Char]
fmt [Char]
inVal =
let fmtHHMM :: [Char]
fmtHHMM = [Char]
fmt [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char]
"%z"
fmtZ :: [Char]
fmtZ = [Char]
fmt [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char]
"Z"
#if MIN_VERSION_time(1,5,0)
pt :: [Char] -> m t
pt [Char]
f = Bool -> TimeLocale -> [Char] -> [Char] -> m t
forall (m :: * -> *) t.
(MonadFail m, ParseTime t) =>
Bool -> TimeLocale -> [Char] -> [Char] -> m t
parseTimeM Bool
True TimeLocale
defaultTimeLocale [Char]
f [Char]
inVal
#else
pt f = parseTime defaultTimeLocale f inVal
#endif
in case [Char] -> Maybe a
forall {m :: * -> *} {t}.
(MonadFail m, ParseTime t) =>
[Char] -> m t
pt [Char]
fmtHHMM of
o :: Maybe a
o@(Just a
_) -> Maybe a
o
Maybe a
_ -> case [Char] -> Maybe a
forall {m :: * -> *} {t}.
(MonadFail m, ParseTime t) =>
[Char] -> m t
pt [Char]
fmtZ of
o :: Maybe a
o@(Just a
_) -> Maybe a
o
Maybe a
_ -> [Char] -> Maybe a
forall {m :: * -> *} {t}.
(MonadFail m, ParseTime t) =>
[Char] -> m t
pt [Char]
fmt
toUTCFormat :: T.Text -> Maybe UTCTime
toUTCFormat :: Text -> Maybe UTCTime
toUTCFormat = [Char] -> [Char] -> Maybe UTCTime
forall a. ParseTime a => [Char] -> [Char] -> Maybe a
toTimeFormat [Char]
"%FT%T%Q" ([Char] -> Maybe UTCTime)
-> (Text -> [Char]) -> Text -> Maybe UTCTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Char]
T.unpack
toDayFormat :: T.Text -> Maybe Day
toDayFormat :: Text -> Maybe Day
toDayFormat = [Char] -> [Char] -> Maybe Day
forall a. ParseTime a => [Char] -> [Char] -> Maybe a
toTimeFormat [Char]
"%F" ([Char] -> Maybe Day) -> (Text -> [Char]) -> Text -> Maybe Day
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Char]
T.unpack
instance ToRDFLabel UTCTime where
toRDFLabel :: UTCTime -> RDFLabel
toRDFLabel = (Text -> ScopedName -> RDFLabel) -> ScopedName -> Text -> RDFLabel
forall a b c. (a -> b -> c) -> b -> a -> c
flip Text -> ScopedName -> RDFLabel
TypedLit ScopedName
xsdDateTime (Text -> RDFLabel) -> (UTCTime -> Text) -> UTCTime -> RDFLabel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Text
T.pack ([Char] -> Text) -> (UTCTime -> [Char]) -> UTCTime -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTCTime -> [Char]
fromUTCFormat
instance FromRDFLabel UTCTime where
fromRDFLabel :: RDFLabel -> Maybe UTCTime
fromRDFLabel = (Text -> Maybe UTCTime) -> ScopedName -> RDFLabel -> Maybe UTCTime
forall a. (Text -> Maybe a) -> ScopedName -> RDFLabel -> Maybe a
fLabel Text -> Maybe UTCTime
toUTCFormat ScopedName
xsdDateTime
instance ToRDFLabel Day where
toRDFLabel :: Day -> RDFLabel
toRDFLabel = (Text -> ScopedName -> RDFLabel) -> ScopedName -> Text -> RDFLabel
forall a b c. (a -> b -> c) -> b -> a -> c
flip Text -> ScopedName -> RDFLabel
TypedLit ScopedName
xsdDate (Text -> RDFLabel) -> (Day -> Text) -> Day -> RDFLabel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Text
T.pack ([Char] -> Text) -> (Day -> [Char]) -> Day -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Day -> [Char]
fromDayFormat
instance FromRDFLabel Day where
fromRDFLabel :: RDFLabel -> Maybe Day
fromRDFLabel = (Text -> Maybe Day) -> ScopedName -> RDFLabel -> Maybe Day
forall a. (Text -> Maybe a) -> ScopedName -> RDFLabel -> Maybe a
fLabel Text -> Maybe Day
toDayFormat ScopedName
xsdDate
instance ToRDFLabel ScopedName where
toRDFLabel :: ScopedName -> RDFLabel
toRDFLabel = ScopedName -> RDFLabel
Res
instance FromRDFLabel ScopedName where
fromRDFLabel :: RDFLabel -> Maybe ScopedName
fromRDFLabel (Res ScopedName
sn) = ScopedName -> Maybe ScopedName
forall a. a -> Maybe a
Just ScopedName
sn
fromRDFLabel RDFLabel
_ = Maybe ScopedName
forall a. Maybe a
Nothing
instance ToRDFLabel QName where
toRDFLabel :: QName -> RDFLabel
toRDFLabel = ScopedName -> RDFLabel
Res (ScopedName -> RDFLabel)
-> (QName -> ScopedName) -> QName -> RDFLabel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe Text -> QName -> ScopedName
makeQNameScopedName Maybe Text
forall a. Maybe a
Nothing
instance FromRDFLabel QName where
fromRDFLabel :: RDFLabel -> Maybe QName
fromRDFLabel (Res ScopedName
sn) = QName -> Maybe QName
forall a. a -> Maybe a
Just (QName -> Maybe QName) -> QName -> Maybe QName
forall a b. (a -> b) -> a -> b
$ ScopedName -> QName
getQName ScopedName
sn
fromRDFLabel RDFLabel
_ = Maybe QName
forall a. Maybe a
Nothing
instance ToRDFLabel URI where
toRDFLabel :: URI -> RDFLabel
toRDFLabel = ScopedName -> RDFLabel
Res (ScopedName -> RDFLabel) -> (URI -> ScopedName) -> URI -> RDFLabel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. URI -> ScopedName
makeURIScopedName
instance FromRDFLabel URI where
fromRDFLabel :: RDFLabel -> Maybe URI
fromRDFLabel (Res ScopedName
sn) = URI -> Maybe URI
forall a. a -> Maybe a
Just (URI -> Maybe URI) -> URI -> Maybe URI
forall a b. (a -> b) -> a -> b
$ ScopedName -> URI
getScopedNameURI ScopedName
sn
fromRDFLabel RDFLabel
_ = Maybe URI
forall a. Maybe a
Nothing
showCanon :: RDFLabel -> String
showCanon :: RDFLabel -> [Char]
showCanon (Res ScopedName
sn) = [Char]
"<" [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ URI -> [Char]
forall a. Show a => a -> [Char]
show (ScopedName -> URI
getScopedNameURI ScopedName
sn) [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char]
">"
showCanon (Lit Text
st) = Text -> [Char]
forall a. Show a => a -> [Char]
show Text
st
showCanon (LangLit Text
st LanguageTag
lang) = Text -> [Char]
quote1Str Text
st [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char]
"@" [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> [Char]
T.unpack (LanguageTag -> Text
fromLangTag LanguageTag
lang)
showCanon (TypedLit Text
st ScopedName
dt) = Text -> [Char]
quote1Str Text
st [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char]
"^^" [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ URI -> [Char]
forall a. Show a => a -> [Char]
show (ScopedName -> URI
getScopedNameURI ScopedName
dt)
showCanon RDFLabel
s = RDFLabel -> [Char]
forall a. Show a => a -> [Char]
show RDFLabel
s
processChar ::
Char
-> (T.Text, Bool)
processChar :: Char -> (Text, Bool)
processChar Char
'"' = (Text
"\\\"", Bool
True)
processChar Char
'\\' = (Text
"\\\\", Bool
True)
processChar Char
'\n' = (Text
"\\n", Bool
True)
processChar Char
'\r' = (Text
"\\r", Bool
True)
processChar Char
'\t' = (Text
"\\t", Bool
True)
processChar Char
'\b' = (Text
"\\b", Bool
True)
processChar Char
'\f' = (Text
"\\u000C", Bool
True)
processChar Char
c =
let nc :: Int
nc = Char -> Int
ord Char
c
four :: Text
four = Text -> Text -> Text
T.append Text
"\\u" (Text -> Text) -> ([Char] -> Text) -> [Char] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Text
T.pack ([Char] -> Text) -> [Char] -> Text
forall a b. (a -> b) -> a -> b
$ [Char] -> Int -> [Char]
forall r. PrintfType r => [Char] -> r
printf [Char]
"%04X" Int
nc
eight :: Text
eight = Text -> Text -> Text
T.append Text
"\\U" (Text -> Text) -> ([Char] -> Text) -> [Char] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Text
T.pack ([Char] -> Text) -> [Char] -> Text
forall a b. (a -> b) -> a -> b
$ [Char] -> Int -> [Char]
forall r. PrintfType r => [Char] -> r
printf [Char]
"%08X" Int
nc
in if Int
nc Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0x20
then (Text
four, Bool
True)
else if Int
nc Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0x7f
then (Char -> Text
T.singleton Char
c, Bool
False)
else if Int
nc Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0x10000
then (Text
four, Bool
True)
else (Text
eight, Bool
True)
convertChar :: Char -> T.Text
convertChar :: Char -> Text
convertChar = (Text, Bool) -> Text
forall a b. (a, b) -> a
fst ((Text, Bool) -> Text) -> (Char -> (Text, Bool)) -> Char -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> (Text, Bool)
processChar
quoteT :: Bool -> T.Text -> T.Text
quoteT :: Bool -> Text -> Text
quoteT Bool
True Text
txt =
let go :: (Text -> t) -> Text -> t
go Text -> t
dl Text
x =
case Text -> Maybe (Char, Text)
T.uncons Text
x of
Just (Char
c, Text
xs) -> (Text -> t) -> Text -> t
go (Text -> t
dl (Text -> t) -> (Text -> Text) -> Text -> t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Text
T.append (Char -> Text
convertChar Char
c)) Text
xs
Maybe (Char, Text)
_ -> Text -> t
dl Text
T.empty
in (Text -> Text) -> Text -> Text
forall {t}. (Text -> t) -> Text -> t
go (Text -> Text -> Text
T.append Text
T.empty) Text
txt
quoteT Bool
_ Text
txt =
let go :: (Text -> t) -> Text -> t
go Text -> t
dl Text
x =
case Text -> Maybe (Char, Text)
T.uncons Text
x of
Just (Char
'"', Text
xs) -> (Text -> t) -> Text -> t
go1 Text -> t
dl Text
xs
Just (Char
'\n', Text
xs) -> (Text -> t) -> Text -> t
go (Text -> t
dl (Text -> t) -> (Text -> Text) -> Text -> t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Text -> Text
T.cons Char
'\n') Text
xs
Just (Char
c, Text
xs) -> (Text -> t) -> Text -> t
go (Text -> t
dl (Text -> t) -> (Text -> Text) -> Text -> t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Text
T.append (Char -> Text
convertChar Char
c)) Text
xs
Maybe (Char, Text)
_ -> Text -> t
dl Text
T.empty
go1 :: (Text -> t) -> Text -> t
go1 Text -> t
dl Text
x =
case Text -> Maybe (Char, Text)
T.uncons Text
x of
Just (Char
'"', Text
xs) -> (Text -> t) -> Text -> t
go2 Text -> t
dl Text
xs
Just (Char
'\n', Text
xs) -> (Text -> t) -> Text -> t
go (Text -> t
dl (Text -> t) -> (Text -> Text) -> Text -> t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Text
T.append Text
"\"\n") Text
xs
Just (Char
'\\', Text
xs) -> (Text -> t) -> Text -> t
go (Text -> t
dl (Text -> t) -> (Text -> Text) -> Text -> t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Text
T.append Text
"\\\"\\\\") Text
xs
Just (Char
c, Text
xs) ->
let (Text
t, Bool
f) = Char -> (Text, Bool)
processChar Char
c
dl' :: Text -> Text
dl' = if Bool
f then Text -> Text -> Text
T.append Text
"\\\"" else Char -> Text -> Text
T.cons Char
'"'
in (Text -> t) -> Text -> t
go (Text -> t
dl (Text -> t) -> (Text -> Text) -> Text -> t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
dl' (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Text
T.append Text
t) Text
xs
Maybe (Char, Text)
_ -> Text -> t
dl Text
"\\\""
go2 :: (Text -> t) -> Text -> t
go2 Text -> t
dl Text
x =
case Text -> Maybe (Char, Text)
T.uncons Text
x of
Just (Char
'"', Text
xs) -> (Text -> t) -> Text -> t
go (Text -> t
dl (Text -> t) -> (Text -> Text) -> Text -> t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Text
T.append Text
"\\\"\\\"\\\"") Text
xs
Just (Char
'\n', Text
xs) -> (Text -> t) -> Text -> t
go (Text -> t
dl (Text -> t) -> (Text -> Text) -> Text -> t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Text
T.append Text
"\"\"\n") Text
xs
Just (Char
'\\', Text
xs) -> (Text -> t) -> Text -> t
go (Text -> t
dl (Text -> t) -> (Text -> Text) -> Text -> t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Text
T.append Text
"\\\"\\\"\\\\") Text
xs
Just (Char
c, Text
xs) ->
let (Text
t, Bool
f) = Char -> (Text, Bool)
processChar Char
c
dl' :: Text -> Text
dl' = Text -> Text -> Text
T.append (if Bool
f then Text
"\\\"\\\"" else Text
"\"\"")
in (Text -> t) -> Text -> t
go (Text -> t
dl (Text -> t) -> (Text -> Text) -> Text -> t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
dl' (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Text
T.append Text
t) Text
xs
Maybe (Char, Text)
_ -> Text -> t
dl Text
"\\\"\\\""
go0 :: (Text -> t) -> Text -> t
go0 Text -> t
dl Text
x =
case Text -> Maybe (Char, Text)
T.uncons Text
x of
Just (Char
'"', Text
xs) -> (Text -> t) -> Text -> t
go0 (Text -> t
dl (Text -> t) -> (Text -> Text) -> Text -> t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Text
T.append Text
"\\\"") Text
xs
Just (Char
'\n', Text
xs) -> (Text -> t) -> Text -> t
forall {t}. (Text -> t) -> Text -> t
go (Text -> t
dl (Text -> t) -> (Text -> Text) -> Text -> t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Text -> Text
T.cons Char
'\n') Text
xs
Just (Char
c, Text
xs) -> (Text -> t) -> Text -> t
forall {t}. (Text -> t) -> Text -> t
go (Text -> t
dl (Text -> t) -> (Text -> Text) -> Text -> t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Text
T.append (Char -> Text
convertChar Char
c)) Text
xs
Maybe (Char, Text)
_ -> Text -> t
dl Text
T.empty
in (Text -> Text) -> Text -> Text
forall {t}. (Text -> t) -> Text -> t
go0 (Text -> Text -> Text
T.append Text
T.empty) Text
txt
quote ::
Bool
-> String
-> String
quote :: Bool -> ShowS
quote Bool
f = Text -> [Char]
T.unpack (Text -> [Char]) -> ([Char] -> Text) -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Text -> Text
quoteT Bool
f (Text -> Text) -> ([Char] -> Text) -> [Char] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Text
T.pack
quote1Str :: T.Text -> String
quote1Str :: Text -> [Char]
quote1Str Text
t = Char
'"' Char -> ShowS
forall a. a -> [a] -> [a]
: Text -> [Char]
T.unpack (Bool -> Text -> Text
quoteT Bool
True Text
t) [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char]
"\""
resRdfType :: RDFLabel
resRdfType :: RDFLabel
resRdfType = ScopedName -> RDFLabel
Res ScopedName
rdfType
resRdfList :: RDFLabel
resRdfList :: RDFLabel
resRdfList = ScopedName -> RDFLabel
Res ScopedName
rdfList
resRdfFirst :: RDFLabel
resRdfFirst :: RDFLabel
resRdfFirst = ScopedName -> RDFLabel
Res ScopedName
rdfFirst
resRdfRest :: RDFLabel
resRdfRest :: RDFLabel
resRdfRest = ScopedName -> RDFLabel
Res ScopedName
rdfRest
resRdfNil :: RDFLabel
resRdfNil :: RDFLabel
resRdfNil = ScopedName -> RDFLabel
Res ScopedName
rdfNil
resRdfsMember :: RDFLabel
resRdfsMember :: RDFLabel
resRdfsMember = ScopedName -> RDFLabel
Res ScopedName
rdfsMember
resRdfdGeneralRestriction :: RDFLabel
resRdfdGeneralRestriction :: RDFLabel
resRdfdGeneralRestriction = ScopedName -> RDFLabel
Res ScopedName
rdfdGeneralRestriction
resRdfdOnProperties :: RDFLabel
resRdfdOnProperties :: RDFLabel
resRdfdOnProperties = ScopedName -> RDFLabel
Res ScopedName
rdfdOnProperties
resRdfdConstraint :: RDFLabel
resRdfdConstraint :: RDFLabel
resRdfdConstraint = ScopedName -> RDFLabel
Res ScopedName
rdfdConstraint
resRdfdMaxCardinality :: RDFLabel
resRdfdMaxCardinality :: RDFLabel
resRdfdMaxCardinality = ScopedName -> RDFLabel
Res ScopedName
rdfdMaxCardinality
resRdfsSeeAlso :: RDFLabel
resRdfsSeeAlso :: RDFLabel
resRdfsSeeAlso = ScopedName -> RDFLabel
Res ScopedName
rdfsSeeAlso
resRdfValue :: RDFLabel
resRdfValue :: RDFLabel
resRdfValue = ScopedName -> RDFLabel
Res ScopedName
rdfValue
resOwlSameAs :: RDFLabel
resOwlSameAs :: RDFLabel
resOwlSameAs = ScopedName -> RDFLabel
Res ScopedName
owlSameAs
resLogImplies :: RDFLabel
resLogImplies :: RDFLabel
resLogImplies = ScopedName -> RDFLabel
Res ScopedName
logImplies
resRdfsLabel :: RDFLabel
resRdfsLabel :: RDFLabel
resRdfsLabel = ScopedName -> RDFLabel
Res ScopedName
rdfsLabel
resRdfsComment :: RDFLabel
= ScopedName -> RDFLabel
Res ScopedName
rdfsComment
resRdfProperty :: RDFLabel
resRdfProperty :: RDFLabel
resRdfProperty = ScopedName -> RDFLabel
Res ScopedName
rdfProperty
resRdfsSubPropertyOf :: RDFLabel
resRdfsSubPropertyOf :: RDFLabel
resRdfsSubPropertyOf = ScopedName -> RDFLabel
Res ScopedName
rdfsSubPropertyOf
resRdfsSubClassOf :: RDFLabel
resRdfsSubClassOf :: RDFLabel
resRdfsSubClassOf = ScopedName -> RDFLabel
Res ScopedName
rdfsSubClassOf
resRdfsClass :: RDFLabel
resRdfsClass :: RDFLabel
resRdfsClass = ScopedName -> RDFLabel
Res ScopedName
rdfsClass
resRdfsLiteral :: RDFLabel
resRdfsLiteral :: RDFLabel
resRdfsLiteral = ScopedName -> RDFLabel
Res ScopedName
rdfsLiteral
resRdfsDatatype :: RDFLabel
resRdfsDatatype :: RDFLabel
resRdfsDatatype = ScopedName -> RDFLabel
Res ScopedName
rdfsDatatype
resRdfXMLLiteral :: RDFLabel
resRdfXMLLiteral :: RDFLabel
resRdfXMLLiteral = ScopedName -> RDFLabel
Res ScopedName
rdfXMLLiteral
resRdfsRange :: RDFLabel
resRdfsRange :: RDFLabel
resRdfsRange = ScopedName -> RDFLabel
Res ScopedName
rdfsRange
resRdfsDomain :: RDFLabel
resRdfsDomain :: RDFLabel
resRdfsDomain = ScopedName -> RDFLabel
Res ScopedName
rdfsDomain
resRdfsContainer :: RDFLabel
resRdfsContainer :: RDFLabel
resRdfsContainer = ScopedName -> RDFLabel
Res ScopedName
rdfsContainer
resRdfBag :: RDFLabel
resRdfBag :: RDFLabel
resRdfBag = ScopedName -> RDFLabel
Res ScopedName
rdfBag
resRdfSeq :: RDFLabel
resRdfSeq :: RDFLabel
resRdfSeq = ScopedName -> RDFLabel
Res ScopedName
rdfSeq
resRdfAlt :: RDFLabel
resRdfAlt :: RDFLabel
resRdfAlt = ScopedName -> RDFLabel
Res ScopedName
rdfAlt
resRdfsContainerMembershipProperty :: RDFLabel
resRdfsContainerMembershipProperty :: RDFLabel
resRdfsContainerMembershipProperty = ScopedName -> RDFLabel
Res ScopedName
rdfsContainerMembershipProperty
resRdfsIsDefinedBy :: RDFLabel
resRdfsIsDefinedBy :: RDFLabel
resRdfsIsDefinedBy = ScopedName -> RDFLabel
Res ScopedName
rdfsIsDefinedBy
resRdfsResource :: RDFLabel
resRdfsResource :: RDFLabel
resRdfsResource = ScopedName -> RDFLabel
Res ScopedName
rdfsResource
resRdfStatement :: RDFLabel
resRdfStatement :: RDFLabel
resRdfStatement = ScopedName -> RDFLabel
Res ScopedName
rdfStatement
resRdfSubject :: RDFLabel
resRdfSubject :: RDFLabel
resRdfSubject = ScopedName -> RDFLabel
Res ScopedName
rdfSubject
resRdfPredicate :: RDFLabel
resRdfPredicate :: RDFLabel
resRdfPredicate = ScopedName -> RDFLabel
Res ScopedName
rdfPredicate
resRdfObject :: RDFLabel
resRdfObject :: RDFLabel
resRdfObject = ScopedName -> RDFLabel
Res ScopedName
rdfObject
resRdfRDF :: RDFLabel
resRdfRDF :: RDFLabel
resRdfRDF = ScopedName -> RDFLabel
Res ScopedName
rdfRDF
resRdfDescription :: RDFLabel
resRdfDescription :: RDFLabel
resRdfDescription = ScopedName -> RDFLabel
Res ScopedName
rdfDescription
resRdfID :: RDFLabel
resRdfID :: RDFLabel
resRdfID = ScopedName -> RDFLabel
Res ScopedName
rdfID
resRdfAbout :: RDFLabel
resRdfAbout :: RDFLabel
resRdfAbout = ScopedName -> RDFLabel
Res ScopedName
rdfAbout
resRdfParseType :: RDFLabel
resRdfParseType :: RDFLabel
resRdfParseType = ScopedName -> RDFLabel
Res ScopedName
rdfParseType
resRdfResource :: RDFLabel
resRdfResource :: RDFLabel
resRdfResource = ScopedName -> RDFLabel
Res ScopedName
rdfResource
resRdfLi :: RDFLabel
resRdfLi :: RDFLabel
resRdfLi = ScopedName -> RDFLabel
Res ScopedName
rdfLi
resRdfNodeID :: RDFLabel
resRdfNodeID :: RDFLabel
resRdfNodeID = ScopedName -> RDFLabel
Res ScopedName
rdfNodeID
resRdfDatatype :: RDFLabel
resRdfDatatype :: RDFLabel
resRdfDatatype = ScopedName -> RDFLabel
Res ScopedName
rdfDatatype
resRdf1 :: RDFLabel
resRdf1 :: RDFLabel
resRdf1 = ScopedName -> RDFLabel
Res ScopedName
rdf1
resRdf2 :: RDFLabel
resRdf2 :: RDFLabel
resRdf2 = ScopedName -> RDFLabel
Res ScopedName
rdf2
resRdfn :: Word32 -> RDFLabel
resRdfn :: Word32 -> RDFLabel
resRdfn = ScopedName -> RDFLabel
Res (ScopedName -> RDFLabel)
-> (Word32 -> ScopedName) -> Word32 -> RDFLabel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> ScopedName
rdfn
isUri :: RDFLabel -> Bool
isUri :: RDFLabel -> Bool
isUri (Res ScopedName
_) = Bool
True
isUri RDFLabel
_ = Bool
False
isLiteral :: RDFLabel -> Bool
isLiteral :: RDFLabel -> Bool
isLiteral (Lit Text
_) = Bool
True
isLiteral (LangLit Text
_ LanguageTag
_) = Bool
True
isLiteral (TypedLit Text
_ ScopedName
_) = Bool
True
isLiteral RDFLabel
_ = Bool
False
isUntypedLiteral :: RDFLabel -> Bool
isUntypedLiteral :: RDFLabel -> Bool
isUntypedLiteral (Lit Text
_) = Bool
True
isUntypedLiteral (LangLit Text
_ LanguageTag
_) = Bool
True
isUntypedLiteral RDFLabel
_ = Bool
False
isTypedLiteral :: RDFLabel -> Bool
isTypedLiteral :: RDFLabel -> Bool
isTypedLiteral (TypedLit Text
_ ScopedName
_) = Bool
True
isTypedLiteral RDFLabel
_ = Bool
False
isXMLLiteral :: RDFLabel -> Bool
isXMLLiteral :: RDFLabel -> Bool
isXMLLiteral = ScopedName -> RDFLabel -> Bool
isDatatyped ScopedName
rdfXMLLiteral
isDatatyped :: ScopedName -> RDFLabel -> Bool
isDatatyped :: ScopedName -> RDFLabel -> Bool
isDatatyped ScopedName
d (TypedLit Text
_ ScopedName
dt) = ScopedName
d ScopedName -> ScopedName -> Bool
forall a. Eq a => a -> a -> Bool
== ScopedName
dt
isDatatyped ScopedName
_ RDFLabel
_ = Bool
False
isMemberProp :: RDFLabel -> Bool
isMemberProp :: RDFLabel -> Bool
isMemberProp (Res ScopedName
sn) =
ScopedName -> Namespace
getScopeNamespace ScopedName
sn Namespace -> Namespace -> Bool
forall a. Eq a => a -> a -> Bool
== Namespace
namespaceRDF Bool -> Bool -> Bool
&&
case Text -> Maybe (Char, Text)
T.uncons (LName -> Text
getLName (ScopedName -> LName
getScopeLocal ScopedName
sn)) of
Just (Char
'_', Text
t) -> (Char -> Bool) -> Text -> Bool
T.all Char -> Bool
isDigit Text
t
Maybe (Char, Text)
_ -> Bool
False
isMemberProp RDFLabel
_ = Bool
False
isBlank :: RDFLabel -> Bool
isBlank :: RDFLabel -> Bool
isBlank (Blank [Char]
_) = Bool
True
isBlank RDFLabel
_ = Bool
False
isQueryVar :: RDFLabel -> Bool
isQueryVar :: RDFLabel -> Bool
isQueryVar (Var [Char]
_) = Bool
True
isQueryVar RDFLabel
_ = Bool
False
getLiteralText :: RDFLabel -> T.Text
getLiteralText :: RDFLabel -> Text
getLiteralText (Lit Text
s) = Text
s
getLiteralText (LangLit Text
s LanguageTag
_) = Text
s
getLiteralText (TypedLit Text
s ScopedName
_) = Text
s
getLiteralText RDFLabel
_ = Text
""
getScopedName :: RDFLabel -> ScopedName
getScopedName :: RDFLabel -> ScopedName
getScopedName (Res ScopedName
sn) = ScopedName
sn
getScopedName RDFLabel
_ = ScopedName
nullScopedName
makeBlank :: RDFLabel -> RDFLabel
makeBlank :: RDFLabel -> RDFLabel
makeBlank (Var [Char]
loc) = [Char] -> RDFLabel
Blank [Char]
loc
makeBlank RDFLabel
lb = RDFLabel
lb
type RDFTriple = Arc RDFLabel
type RDFArcSet = ArcSet RDFLabel
toRDFTriple ::
(ToRDFLabel s, ToRDFLabel p, ToRDFLabel o)
=> s
-> p
-> o
-> RDFTriple
toRDFTriple :: forall s p o.
(ToRDFLabel s, ToRDFLabel p, ToRDFLabel o) =>
s -> p -> o -> RDFTriple
toRDFTriple s
s p
p o
o =
RDFLabel -> RDFLabel -> RDFLabel -> RDFTriple
forall lb. lb -> lb -> lb -> Arc lb
Arc (s -> RDFLabel
forall a. ToRDFLabel a => a -> RDFLabel
toRDFLabel s
s) (p -> RDFLabel
forall a. ToRDFLabel a => a -> RDFLabel
toRDFLabel p
p) (o -> RDFLabel
forall a. ToRDFLabel a => a -> RDFLabel
toRDFLabel o
o)
fromRDFTriple ::
(FromRDFLabel s, FromRDFLabel p, FromRDFLabel o)
=> RDFTriple
-> Maybe (s, p, o)
fromRDFTriple :: forall s p o.
(FromRDFLabel s, FromRDFLabel p, FromRDFLabel o) =>
RDFTriple -> Maybe (s, p, o)
fromRDFTriple (Arc RDFLabel
s RDFLabel
p RDFLabel
o) =
(,,) (s -> p -> o -> (s, p, o))
-> Maybe s -> Maybe (p -> o -> (s, p, o))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RDFLabel -> Maybe s
forall a. FromRDFLabel a => RDFLabel -> Maybe a
fromRDFLabel RDFLabel
s Maybe (p -> o -> (s, p, o)) -> Maybe p -> Maybe (o -> (s, p, o))
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RDFLabel -> Maybe p
forall a. FromRDFLabel a => RDFLabel -> Maybe a
fromRDFLabel RDFLabel
p Maybe (o -> (s, p, o)) -> Maybe o -> Maybe (s, p, o)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> RDFLabel -> Maybe o
forall a. FromRDFLabel a => RDFLabel -> Maybe a
fromRDFLabel RDFLabel
o
type NamespaceMap = M.Map (Maybe T.Text) URI
emptyNamespaceMap :: NamespaceMap
emptyNamespaceMap :: NamespaceMap
emptyNamespaceMap = NamespaceMap
forall k a. Map k a
M.empty
data LookupFormula lb gr = Formula
{ forall lb gr. LookupFormula lb gr -> lb
formLabel :: lb
, forall lb gr. LookupFormula lb gr -> gr
formGraph :: gr
}
instance (Eq lb, Eq gr) => Eq (LookupFormula lb gr) where
LookupFormula lb gr
f1 == :: LookupFormula lb gr -> LookupFormula lb gr -> Bool
== LookupFormula lb gr
f2 = LookupFormula lb gr -> lb
forall lb gr. LookupFormula lb gr -> lb
formLabel LookupFormula lb gr
f1 lb -> lb -> Bool
forall a. Eq a => a -> a -> Bool
== LookupFormula lb gr -> lb
forall lb gr. LookupFormula lb gr -> lb
formLabel LookupFormula lb gr
f2 Bool -> Bool -> Bool
&&
LookupFormula lb gr -> gr
forall lb gr. LookupFormula lb gr -> gr
formGraph LookupFormula lb gr
f1 gr -> gr -> Bool
forall a. Eq a => a -> a -> Bool
== LookupFormula lb gr -> gr
forall lb gr. LookupFormula lb gr -> gr
formGraph LookupFormula lb gr
f2
instance (Ord lb, Ord gr) => Ord (LookupFormula lb gr) where
(Formula lb
a1 gr
b1) compare :: LookupFormula lb gr -> LookupFormula lb gr -> Ordering
`compare` (Formula lb
a2 gr
b2) =
(lb
a1,gr
b1) (lb, gr) -> (lb, gr) -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` (lb
a2,gr
b2)
type Formula lb = LookupFormula lb (NSGraph lb)
instance (Label lb) => Show (Formula lb)
where
show :: Formula lb -> [Char]
show (Formula lb
l NSGraph lb
g) = lb -> [Char]
forall a. Show a => a -> [Char]
show lb
l [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char]
" :- { " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char] -> NSGraph lb -> [Char]
forall lb. Label lb => [Char] -> NSGraph lb -> [Char]
showArcs [Char]
" " NSGraph lb
g [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char]
" }"
type FormulaMap lb = M.Map lb (NSGraph lb)
emptyFormulaMap :: FormulaMap RDFLabel
emptyFormulaMap :: FormulaMap RDFLabel
emptyFormulaMap = FormulaMap RDFLabel
forall k a. Map k a
M.empty
fmapFormulaMap :: (Ord a) => (a -> a) -> FormulaMap a -> FormulaMap a
fmapFormulaMap :: forall a. Ord a => (a -> a) -> FormulaMap a -> FormulaMap a
fmapFormulaMap a -> a
f FormulaMap a
m = [(a, NSGraph a)] -> FormulaMap a
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ([(a, NSGraph a)] -> FormulaMap a)
-> [(a, NSGraph a)] -> FormulaMap a
forall a b. (a -> b) -> a -> b
$ ((a, NSGraph a) -> (a, NSGraph a))
-> [(a, NSGraph a)] -> [(a, NSGraph a)]
forall a b. (a -> b) -> [a] -> [b]
map (a -> a
f (a -> a)
-> (NSGraph a -> NSGraph a) -> (a, NSGraph a) -> (a, NSGraph a)
forall b c b' c'. (b -> c) -> (b' -> c') -> (b, b') -> (c, c')
forall (a :: * -> * -> *) b c b' c'.
Arrow a =>
a b c -> a b' c' -> a (b, b') (c, c')
*** (a -> a) -> NSGraph a -> NSGraph a
forall lb. Ord lb => (lb -> lb) -> NSGraph lb -> NSGraph lb
fmapNSGraph a -> a
f) ([(a, NSGraph a)] -> [(a, NSGraph a)])
-> [(a, NSGraph a)] -> [(a, NSGraph a)]
forall a b. (a -> b) -> a -> b
$ FormulaMap a -> [(a, NSGraph a)]
forall k a. Map k a -> [(k, a)]
M.assocs FormulaMap a
m
traverseFormulaMap ::
(Applicative f, Ord a)
=> (a -> f a) -> FormulaMap a -> f (FormulaMap a)
traverseFormulaMap :: forall (f :: * -> *) a.
(Applicative f, Ord a) =>
(a -> f a) -> FormulaMap a -> f (FormulaMap a)
traverseFormulaMap a -> f a
f = (NSGraph a -> f (NSGraph a))
-> Map a (NSGraph a) -> f (Map a (NSGraph a))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Map a a -> f (Map a b)
Traversable.traverse ((a -> f a) -> NSGraph a -> f (NSGraph a)
forall (f :: * -> *) a.
(Applicative f, Ord a) =>
(a -> f a) -> NSGraph a -> f (NSGraph a)
traverseFormula a -> f a
f)
traverseFormula ::
(Applicative f, Ord a)
=> (a -> f a) -> NSGraph a -> f (NSGraph a)
traverseFormula :: forall (f :: * -> *) a.
(Applicative f, Ord a) =>
(a -> f a) -> NSGraph a -> f (NSGraph a)
traverseFormula = (a -> f a) -> NSGraph a -> f (NSGraph a)
forall (f :: * -> *) a.
(Applicative f, Ord a) =>
(a -> f a) -> NSGraph a -> f (NSGraph a)
traverseNSGraph
data NSGraph lb = NSGraph
{ forall lb. NSGraph lb -> NamespaceMap
namespaces :: NamespaceMap
, forall lb. NSGraph lb -> FormulaMap lb
formulae :: FormulaMap lb
, forall lb. NSGraph lb -> ArcSet lb
statements :: ArcSet lb
}
instance LDGraph NSGraph lb where
emptyGraph :: NSGraph lb
emptyGraph = NamespaceMap -> FormulaMap lb -> ArcSet lb -> NSGraph lb
forall lb. NamespaceMap -> FormulaMap lb -> ArcSet lb -> NSGraph lb
NSGraph NamespaceMap
emptyNamespaceMap FormulaMap lb
forall k a. Map k a
M.empty ArcSet lb
forall a. Set a
S.empty
getArcs :: NSGraph lb -> ArcSet lb
getArcs = NSGraph lb -> ArcSet lb
forall lb. NSGraph lb -> ArcSet lb
statements
setArcs :: NSGraph lb -> ArcSet lb -> NSGraph lb
setArcs NSGraph lb
g ArcSet lb
as = NSGraph lb
g { statements=as }
instance (Label lb) => Semigroup (NSGraph lb) where
<> :: NSGraph lb -> NSGraph lb -> NSGraph lb
(<>) = NSGraph lb -> NSGraph lb -> NSGraph lb
forall lb. Label lb => NSGraph lb -> NSGraph lb -> NSGraph lb
merge
instance (Label lb) => Monoid (NSGraph lb) where
mempty :: NSGraph lb
mempty = NSGraph lb
forall (lg :: * -> *) lb. LDGraph lg lb => lg lb
emptyGraph
#if !(MIN_VERSION_base(4, 11, 0))
mappend = (<>)
#endif
fmapNSGraph :: (Ord lb) => (lb -> lb) -> NSGraph lb -> NSGraph lb
fmapNSGraph :: forall lb. Ord lb => (lb -> lb) -> NSGraph lb -> NSGraph lb
fmapNSGraph lb -> lb
f (NSGraph NamespaceMap
ns FormulaMap lb
fml ArcSet lb
stmts) =
NamespaceMap -> FormulaMap lb -> ArcSet lb -> NSGraph lb
forall lb. NamespaceMap -> FormulaMap lb -> ArcSet lb -> NSGraph lb
NSGraph NamespaceMap
ns ((lb -> lb) -> FormulaMap lb -> FormulaMap lb
forall a. Ord a => (a -> a) -> FormulaMap a -> FormulaMap a
fmapFormulaMap lb -> lb
f FormulaMap lb
fml) (((Arc lb -> Arc lb) -> ArcSet lb -> ArcSet lb
forall b a. Ord b => (a -> b) -> Set a -> Set b
S.map ((Arc lb -> Arc lb) -> ArcSet lb -> ArcSet lb)
-> (Arc lb -> Arc lb) -> ArcSet lb -> ArcSet lb
forall a b. (a -> b) -> a -> b
$ (lb -> lb) -> Arc lb -> Arc lb
forall a b. (a -> b) -> Arc a -> Arc b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap lb -> lb
f) ArcSet lb
stmts)
traverseNSGraph ::
(Applicative f, Ord a)
=> (a -> f a) -> NSGraph a -> f (NSGraph a)
traverseNSGraph :: forall (f :: * -> *) a.
(Applicative f, Ord a) =>
(a -> f a) -> NSGraph a -> f (NSGraph a)
traverseNSGraph a -> f a
f (NSGraph NamespaceMap
ns FormulaMap a
fml ArcSet a
stmts) =
NamespaceMap -> FormulaMap a -> ArcSet a -> NSGraph a
forall lb. NamespaceMap -> FormulaMap lb -> ArcSet lb -> NSGraph lb
NSGraph NamespaceMap
ns (FormulaMap a -> ArcSet a -> NSGraph a)
-> f (FormulaMap a) -> f (ArcSet a -> NSGraph a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> f a) -> FormulaMap a -> f (FormulaMap a)
forall (f :: * -> *) a.
(Applicative f, Ord a) =>
(a -> f a) -> FormulaMap a -> f (FormulaMap a)
traverseFormulaMap a -> f a
f FormulaMap a
fml f (ArcSet a -> NSGraph a) -> f (ArcSet a) -> f (NSGraph a)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((Arc a -> f (Arc a)) -> ArcSet a -> f (ArcSet a)
forall (f :: * -> *) b a.
(Applicative f, Ord b) =>
(a -> f b) -> Set a -> f (Set b)
traverseSet ((Arc a -> f (Arc a)) -> ArcSet a -> f (ArcSet a))
-> (Arc a -> f (Arc a)) -> ArcSet a -> f (ArcSet a)
forall a b. (a -> b) -> a -> b
$ (a -> f a) -> Arc a -> f (Arc a)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Arc a -> f (Arc b)
Traversable.traverse a -> f a
f) ArcSet a
stmts
traverseSet ::
(Applicative f, Ord b)
=> (a -> f b) -> S.Set a -> f (S.Set b)
traverseSet :: forall (f :: * -> *) b a.
(Applicative f, Ord b) =>
(a -> f b) -> Set a -> f (Set b)
traverseSet a -> f b
f = (a -> f (Set b) -> f (Set b)) -> f (Set b) -> Set a -> f (Set b)
forall a b. (a -> b -> b) -> b -> Set a -> b
S.foldr a -> f (Set b) -> f (Set b)
cons (Set b -> f (Set b)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Set b
forall a. Set a
S.empty)
where
cons :: a -> f (Set b) -> f (Set b)
cons a
x f (Set b)
s = b -> Set b -> Set b
forall a. Ord a => a -> Set a -> Set a
S.insert (b -> Set b -> Set b) -> f b -> f (Set b -> Set b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
x f (Set b -> Set b) -> f (Set b) -> f (Set b)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> f (Set b)
s
instance (Label lb) => Eq (NSGraph lb) where
== :: NSGraph lb -> NSGraph lb -> Bool
(==) = NSGraph lb -> NSGraph lb -> Bool
forall lb. Label lb => NSGraph lb -> NSGraph lb -> Bool
grEq
instance (Label lb) => Ord (NSGraph lb) where
(NSGraph NamespaceMap
_ FormulaMap lb
fml1 ArcSet lb
stmts1) compare :: NSGraph lb -> NSGraph lb -> Ordering
`compare` (NSGraph NamespaceMap
_ FormulaMap lb
fml2 ArcSet lb
stmts2) =
(FormulaMap lb
fml1,ArcSet lb
stmts1) (FormulaMap lb, ArcSet lb)
-> (FormulaMap lb, ArcSet lb) -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` (FormulaMap lb
fml2,ArcSet lb
stmts2)
instance (Label lb) => Show (NSGraph lb) where
show :: NSGraph lb -> [Char]
show = [Char] -> NSGraph lb -> [Char]
forall lb. Label lb => [Char] -> NSGraph lb -> [Char]
grShow [Char]
""
showList :: [NSGraph lb] -> ShowS
showList = [Char] -> [NSGraph lb] -> ShowS
forall lb. Label lb => [Char] -> [NSGraph lb] -> ShowS
grShowList [Char]
""
getNamespaces :: NSGraph lb -> NamespaceMap
getNamespaces :: forall lb. NSGraph lb -> NamespaceMap
getNamespaces = NSGraph lb -> NamespaceMap
forall lb. NSGraph lb -> NamespaceMap
namespaces
setNamespaces :: NamespaceMap -> NSGraph lb -> NSGraph lb
setNamespaces :: forall lb. NamespaceMap -> NSGraph lb -> NSGraph lb
setNamespaces NamespaceMap
ns NSGraph lb
g = NSGraph lb
g { namespaces=ns }
getFormulae :: NSGraph lb -> FormulaMap lb
getFormulae :: forall lb. NSGraph lb -> FormulaMap lb
getFormulae = NSGraph lb -> FormulaMap lb
forall lb. NSGraph lb -> FormulaMap lb
formulae
setFormulae :: FormulaMap lb -> NSGraph lb -> NSGraph lb
setFormulae :: forall lb. FormulaMap lb -> NSGraph lb -> NSGraph lb
setFormulae FormulaMap lb
fs NSGraph lb
g = NSGraph lb
g { formulae=fs }
getFormula :: (Label lb) => NSGraph lb -> lb -> Maybe (NSGraph lb)
getFormula :: forall lb. Label lb => NSGraph lb -> lb -> Maybe (NSGraph lb)
getFormula NSGraph lb
g lb
l = lb -> Map lb (NSGraph lb) -> Maybe (NSGraph lb)
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup lb
l (NSGraph lb -> Map lb (NSGraph lb)
forall lb. NSGraph lb -> FormulaMap lb
formulae NSGraph lb
g)
setFormula :: (Label lb) => Formula lb -> NSGraph lb -> NSGraph lb
setFormula :: forall lb. Label lb => Formula lb -> NSGraph lb -> NSGraph lb
setFormula (Formula lb
fn NSGraph lb
fg) NSGraph lb
g = NSGraph lb
g { formulae = M.insert fn fg (formulae g) }
addArc :: (Label lb) => Arc lb -> NSGraph lb -> NSGraph lb
addArc :: forall lb. Label lb => Arc lb -> NSGraph lb -> NSGraph lb
addArc Arc lb
ar = (ArcSet lb -> ArcSet lb) -> NSGraph lb -> NSGraph lb
forall (lg :: * -> *) lb.
LDGraph lg lb =>
(ArcSet lb -> ArcSet lb) -> lg lb -> lg lb
update (Arc lb -> ArcSet lb -> ArcSet lb
forall a. Ord a => a -> Set a -> Set a
S.insert Arc lb
ar)
grShowList :: (Label lb) => String -> [NSGraph lb] -> String -> String
grShowList :: forall lb. Label lb => [Char] -> [NSGraph lb] -> ShowS
grShowList [Char]
_ [] = [Char] -> ShowS
showString [Char]
"[no graphs]"
grShowList [Char]
p (NSGraph lb
g:[NSGraph lb]
gs) = Char -> ShowS
showChar Char
'[' ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> ShowS
showString ([Char] -> NSGraph lb -> [Char]
forall lb. Label lb => [Char] -> NSGraph lb -> [Char]
grShow [Char]
pp NSGraph lb
g) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [NSGraph lb] -> ShowS
forall lb. Label lb => [NSGraph lb] -> ShowS
showl [NSGraph lb]
gs
where
showl :: [NSGraph lb] -> ShowS
showl [] = Char -> ShowS
showChar Char
']'
showl (NSGraph lb
h:[NSGraph lb]
hs) = [Char] -> ShowS
showString ([Char]
",\n " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char]
p [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char] -> NSGraph lb -> [Char]
forall lb. Label lb => [Char] -> NSGraph lb -> [Char]
grShow [Char]
pp NSGraph lb
h) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [NSGraph lb] -> ShowS
showl [NSGraph lb]
hs
pp :: [Char]
pp = Char
' 'Char -> ShowS
forall a. a -> [a] -> [a]
:[Char]
p
grShow :: (Label lb) => String -> NSGraph lb -> String
grShow :: forall lb. Label lb => [Char] -> NSGraph lb -> [Char]
grShow [Char]
p NSGraph lb
g =
[Char]
"Graph, formulae: " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char]
showForm [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char]
"\n" [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++
[Char]
p [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char]
"arcs: " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char] -> NSGraph lb -> [Char]
forall lb. Label lb => [Char] -> NSGraph lb -> [Char]
showArcs [Char]
p NSGraph lb
g
where
showForm :: [Char]
showForm = (LookupFormula lb (NSGraph lb) -> [Char])
-> [LookupFormula lb (NSGraph lb)] -> [Char]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (([Char]
pp [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++) ShowS
-> (LookupFormula lb (NSGraph lb) -> [Char])
-> LookupFormula lb (NSGraph lb)
-> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LookupFormula lb (NSGraph lb) -> [Char]
forall a. Show a => a -> [Char]
show) [LookupFormula lb (NSGraph lb)]
fml
fml :: [LookupFormula lb (NSGraph lb)]
fml = ((lb, NSGraph lb) -> LookupFormula lb (NSGraph lb))
-> [(lb, NSGraph lb)] -> [LookupFormula lb (NSGraph lb)]
forall a b. (a -> b) -> [a] -> [b]
map ((lb -> NSGraph lb -> LookupFormula lb (NSGraph lb))
-> (lb, NSGraph lb) -> LookupFormula lb (NSGraph lb)
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry lb -> NSGraph lb -> LookupFormula lb (NSGraph lb)
forall lb gr. lb -> gr -> LookupFormula lb gr
Formula) ([(lb, NSGraph lb)] -> [LookupFormula lb (NSGraph lb)])
-> [(lb, NSGraph lb)] -> [LookupFormula lb (NSGraph lb)]
forall a b. (a -> b) -> a -> b
$ Map lb (NSGraph lb) -> [(lb, NSGraph lb)]
forall k a. Map k a -> [(k, a)]
M.assocs (NSGraph lb -> Map lb (NSGraph lb)
forall lb. NSGraph lb -> FormulaMap lb
getFormulae NSGraph lb
g)
pp :: [Char]
pp = [Char]
"\n " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char]
p
showArcs :: (Label lb) => String -> NSGraph lb -> String
showArcs :: forall lb. Label lb => [Char] -> NSGraph lb -> [Char]
showArcs [Char]
p NSGraph lb
g = (Arc lb -> ShowS) -> [Char] -> Set (Arc lb) -> [Char]
forall a b. (a -> b -> b) -> b -> Set a -> b
S.foldr ([Char] -> ShowS
forall a. [a] -> [a] -> [a]
(++) ([Char] -> ShowS) -> (Arc lb -> [Char]) -> Arc lb -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Char]
pp [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++) ShowS -> (Arc lb -> [Char]) -> Arc lb -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Arc lb -> [Char]
forall a. Show a => a -> [Char]
show) [Char]
"" (NSGraph lb -> Set (Arc lb)
forall (lg :: * -> *) lb. LDGraph lg lb => lg lb -> ArcSet lb
getArcs NSGraph lb
g)
where
pp :: [Char]
pp = [Char]
"\n " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char]
p
grEq :: (Label lb) => NSGraph lb -> NSGraph lb -> Bool
grEq :: forall lb. Label lb => NSGraph lb -> NSGraph lb -> Bool
grEq NSGraph lb
g1 = (Bool, LabelMap (ScopedLabel lb)) -> Bool
forall a b. (a, b) -> a
fst ((Bool, LabelMap (ScopedLabel lb)) -> Bool)
-> (NSGraph lb -> (Bool, LabelMap (ScopedLabel lb)))
-> NSGraph lb
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NSGraph lb -> NSGraph lb -> (Bool, LabelMap (ScopedLabel lb))
forall lb.
Label lb =>
NSGraph lb -> NSGraph lb -> (Bool, LabelMap (ScopedLabel lb))
grMatchMap NSGraph lb
g1
grMatchMap :: (Label lb) =>
NSGraph lb -> NSGraph lb -> (Bool, LabelMap (ScopedLabel lb))
grMatchMap :: forall lb.
Label lb =>
NSGraph lb -> NSGraph lb -> (Bool, LabelMap (ScopedLabel lb))
grMatchMap NSGraph lb
g1 NSGraph lb
g2 =
(lb -> lb -> Bool)
-> ArcSet lb -> ArcSet lb -> (Bool, LabelMap (ScopedLabel lb))
forall lb.
Label lb =>
(lb -> lb -> Bool)
-> ArcSet lb -> ArcSet lb -> (Bool, LabelMap (ScopedLabel lb))
graphMatch lb -> lb -> Bool
matchable (NSGraph lb -> ArcSet lb
forall (lg :: * -> *) lb. LDGraph lg lb => lg lb -> ArcSet lb
getArcs NSGraph lb
g1) (NSGraph lb -> ArcSet lb
forall (lg :: * -> *) lb. LDGraph lg lb => lg lb -> ArcSet lb
getArcs NSGraph lb
g2)
where
matchable :: lb -> lb -> Bool
matchable lb
l1 lb
l2 = NSGraph lb -> lb -> Maybe (NSGraph lb)
forall {k}. Ord k => NSGraph k -> k -> Maybe (NSGraph k)
mapFormula NSGraph lb
g1 lb
l1 Maybe (NSGraph lb) -> Maybe (NSGraph lb) -> Bool
forall a. Eq a => a -> a -> Bool
== NSGraph lb -> lb -> Maybe (NSGraph lb)
forall {k}. Ord k => NSGraph k -> k -> Maybe (NSGraph k)
mapFormula NSGraph lb
g2 lb
l2
mapFormula :: NSGraph k -> k -> Maybe (NSGraph k)
mapFormula NSGraph k
g k
l = k -> Map k (NSGraph k) -> Maybe (NSGraph k)
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup k
l (NSGraph k -> Map k (NSGraph k)
forall lb. NSGraph lb -> FormulaMap lb
getFormulae NSGraph k
g)
merge :: (Label lb) => NSGraph lb -> NSGraph lb -> NSGraph lb
merge :: forall lb. Label lb => NSGraph lb -> NSGraph lb -> NSGraph lb
merge NSGraph lb
gr1 NSGraph lb
gr2 =
let bn1 :: [lb]
bn1 = Set lb -> [lb]
forall a. Set a -> [a]
S.toList (Set lb -> [lb]) -> Set lb -> [lb]
forall a b. (a -> b) -> a -> b
$ (lb -> Bool) -> NSGraph lb -> Set lb
forall lb. Label lb => (lb -> Bool) -> NSGraph lb -> Set lb
allLabels lb -> Bool
forall lb. Label lb => lb -> Bool
labelIsVar NSGraph lb
gr1
bn2 :: [lb]
bn2 = Set lb -> [lb]
forall a. Set a -> [a]
S.toList (Set lb -> [lb]) -> Set lb -> [lb]
forall a b. (a -> b) -> a -> b
$ (lb -> Bool) -> NSGraph lb -> Set lb
forall lb. Label lb => (lb -> Bool) -> NSGraph lb -> Set lb
allLabels lb -> Bool
forall lb. Label lb => lb -> Bool
labelIsVar NSGraph lb
gr2
dupbn :: [lb]
dupbn = [lb] -> [lb] -> [lb]
forall a. Eq a => [a] -> [a] -> [a]
intersect [lb]
bn1 [lb]
bn2
allbn :: [lb]
allbn = [lb] -> [lb] -> [lb]
forall a. Eq a => [a] -> [a] -> [a]
union [lb]
bn1 [lb]
bn2
in NSGraph lb -> NSGraph lb -> NSGraph lb
forall (lg :: * -> *) lb.
(LDGraph lg lb, Ord lb) =>
lg lb -> lg lb -> lg lb
addGraphs NSGraph lb
gr1 ([lb] -> [lb] -> (lb -> lb) -> NSGraph lb -> NSGraph lb
forall lb.
Label lb =>
[lb] -> [lb] -> (lb -> lb) -> NSGraph lb -> NSGraph lb
remapLabels [lb]
dupbn [lb]
allbn lb -> lb
forall a. a -> a
id NSGraph lb
gr2)
allLabels :: (Label lb) => (lb -> Bool) -> NSGraph lb -> S.Set lb
allLabels :: forall lb. Label lb => (lb -> Bool) -> NSGraph lb -> Set lb
allLabels lb -> Bool
p NSGraph lb
gr = (lb -> Bool) -> Set lb -> Set lb
forall a. (a -> Bool) -> Set a -> Set a
S.filter lb -> Bool
p ((lb -> Bool) -> Set lb -> Set lb -> Set lb
forall lb. Label lb => (lb -> Bool) -> Set lb -> Set lb -> Set lb
unionNodes lb -> Bool
p ((lb -> Bool) -> NSGraph lb -> Set lb
forall lb. Label lb => (lb -> Bool) -> NSGraph lb -> Set lb
formulaNodes lb -> Bool
p NSGraph lb
gr) (NSGraph lb -> Set lb
forall (lg :: * -> *) lb.
(LDGraph lg lb, Ord lb) =>
lg lb -> Set lb
labels NSGraph lb
gr) )
allNodes :: (Label lb) => (lb -> Bool) -> NSGraph lb -> S.Set lb
allNodes :: forall lb. Label lb => (lb -> Bool) -> NSGraph lb -> Set lb
allNodes lb -> Bool
p = (lb -> Bool) -> Set lb -> Set lb -> Set lb
forall lb. Label lb => (lb -> Bool) -> Set lb -> Set lb -> Set lb
unionNodes lb -> Bool
p Set lb
forall a. Set a
S.empty (Set lb -> Set lb)
-> (NSGraph lb -> Set lb) -> NSGraph lb -> Set lb
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NSGraph lb -> Set lb
forall (lg :: * -> *) lb.
(LDGraph lg lb, Ord lb) =>
lg lb -> Set lb
nodes
formulaNodes :: (Label lb) => (lb -> Bool) -> NSGraph lb -> S.Set lb
formulaNodes :: forall lb. Label lb => (lb -> Bool) -> NSGraph lb -> Set lb
formulaNodes lb -> Bool
p NSGraph lb
gr = (Set lb -> Set lb -> Set lb) -> Set lb -> [Set lb] -> Set lb
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' ((lb -> Bool) -> Set lb -> Set lb -> Set lb
forall lb. Label lb => (lb -> Bool) -> Set lb -> Set lb -> Set lb
unionNodes lb -> Bool
p) Set lb
fkeys ((NSGraph lb -> Set lb) -> [NSGraph lb] -> [Set lb]
forall a b. (a -> b) -> [a] -> [b]
map ((lb -> Bool) -> NSGraph lb -> Set lb
forall lb. Label lb => (lb -> Bool) -> NSGraph lb -> Set lb
allLabels lb -> Bool
p) [NSGraph lb]
fvals)
where
fm :: FormulaMap lb
fm = NSGraph lb -> FormulaMap lb
forall lb. NSGraph lb -> FormulaMap lb
formulae NSGraph lb
gr
fvals :: [NSGraph lb]
fvals = FormulaMap lb -> [NSGraph lb]
forall k a. Map k a -> [a]
M.elems FormulaMap lb
fm
fkeys :: Set lb
fkeys = (lb -> Bool) -> Set lb -> Set lb
forall a. (a -> Bool) -> Set a -> Set a
S.filter lb -> Bool
p (Set lb -> Set lb) -> Set lb -> Set lb
forall a b. (a -> b) -> a -> b
$ [lb] -> Set lb
forall a. Ord a => [a] -> Set a
S.fromList ([lb] -> Set lb) -> [lb] -> Set lb
forall a b. (a -> b) -> a -> b
$ FormulaMap lb -> [lb]
forall k a. Map k a -> [k]
M.keys FormulaMap lb
fm
unionNodes :: (Label lb) => (lb -> Bool) -> S.Set lb -> S.Set lb -> S.Set lb
unionNodes :: forall lb. Label lb => (lb -> Bool) -> Set lb -> Set lb -> Set lb
unionNodes lb -> Bool
p Set lb
ls1 Set lb
ls2 = Set lb
ls1 Set lb -> Set lb -> Set lb
forall a. Ord a => Set a -> Set a -> Set a
`S.union` (lb -> Bool) -> Set lb -> Set lb
forall a. (a -> Bool) -> Set a -> Set a
S.filter lb -> Bool
p Set lb
ls2
remapLabels ::
(Label lb)
=> [lb]
-> [lb]
-> (lb -> lb)
-> NSGraph lb
-> NSGraph lb
remapLabels :: forall lb.
Label lb =>
[lb] -> [lb] -> (lb -> lb) -> NSGraph lb -> NSGraph lb
remapLabels [lb]
dupbn [lb]
allbn lb -> lb
cnvbn =
(lb -> lb) -> NSGraph lb -> NSGraph lb
forall lb. Ord lb => (lb -> lb) -> NSGraph lb -> NSGraph lb
fmapNSGraph ([lb] -> [lb] -> (lb -> lb) -> lb -> lb
forall lb. Label lb => [lb] -> [lb] -> (lb -> lb) -> lb -> lb
mapnode [lb]
dupbn [lb]
allbn lb -> lb
cnvbn)
remapLabelList ::
(Label lb)
=> [lb]
-> [lb]
-> [(lb,lb)]
remapLabelList :: forall lb. Label lb => [lb] -> [lb] -> [(lb, lb)]
remapLabelList [lb]
remap [lb]
avoid = [lb] -> [lb] -> (lb -> lb) -> [(lb, lb)] -> [(lb, lb)]
forall lb.
Label lb =>
[lb] -> [lb] -> (lb -> lb) -> [(lb, lb)] -> [(lb, lb)]
maplist [lb]
remap [lb]
avoid lb -> lb
forall a. a -> a
id []
mapnode ::
(Label lb) => [lb] -> [lb] -> (lb -> lb) -> lb -> lb
mapnode :: forall lb. Label lb => [lb] -> [lb] -> (lb -> lb) -> lb -> lb
mapnode [lb]
dupbn [lb]
allbn lb -> lb
cnvbn lb
nv =
lb -> lb -> Map lb lb -> lb
forall k a. Ord k => a -> k -> Map k a -> a
M.findWithDefault lb
nv lb
nv (Map lb lb -> lb) -> Map lb lb -> lb
forall a b. (a -> b) -> a -> b
$ [(lb, lb)] -> Map lb lb
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ([(lb, lb)] -> Map lb lb) -> [(lb, lb)] -> Map lb lb
forall a b. (a -> b) -> a -> b
$ [lb] -> [lb] -> (lb -> lb) -> [(lb, lb)] -> [(lb, lb)]
forall lb.
Label lb =>
[lb] -> [lb] -> (lb -> lb) -> [(lb, lb)] -> [(lb, lb)]
maplist [lb]
dupbn [lb]
allbn lb -> lb
cnvbn []
maplist ::
(Label lb)
=> [lb]
-> [lb]
-> (lb -> lb)
-> [(lb,lb)]
-> [(lb,lb)]
maplist :: forall lb.
Label lb =>
[lb] -> [lb] -> (lb -> lb) -> [(lb, lb)] -> [(lb, lb)]
maplist [] [lb]
_ lb -> lb
_ [(lb, lb)]
mapbn = [(lb, lb)]
mapbn
maplist (lb
dn:[lb]
dupbn) [lb]
allbn lb -> lb
cnvbn [(lb, lb)]
mapbn = [lb] -> [lb] -> (lb -> lb) -> [(lb, lb)] -> [(lb, lb)]
forall lb.
Label lb =>
[lb] -> [lb] -> (lb -> lb) -> [(lb, lb)] -> [(lb, lb)]
maplist [lb]
dupbn [lb]
allbn' lb -> lb
cnvbn [(lb, lb)]
mapbn'
where
dnmap :: lb
dnmap = lb -> [lb] -> lb
forall lb. Label lb => lb -> [lb] -> lb
newNode (lb -> lb
cnvbn lb
dn) [lb]
allbn
mapbn' :: [(lb, lb)]
mapbn' = (lb
dn,lb
dnmap)(lb, lb) -> [(lb, lb)] -> [(lb, lb)]
forall a. a -> [a] -> [a]
:[(lb, lb)]
mapbn
allbn' :: [lb]
allbn' = lb
dnmaplb -> [lb] -> [lb]
forall a. a -> [a] -> [a]
:[lb]
allbn
newNode :: (Label lb) => lb -> [lb] -> lb
newNode :: forall lb. Label lb => lb -> [lb] -> lb
newNode lb
dn [lb]
existnodes =
case lb -> [lb] -> [lb]
forall lb. Label lb => lb -> [lb] -> [lb]
newNodes lb
dn [lb]
existnodes of
(lb
n:[lb]
_) -> lb
n
[] -> [Char] -> lb
forall a. HasCallStack => [Char] -> a
error [Char]
"unable to create a new node; should be impossible"
newNodes :: (Label lb) => lb -> [lb] -> [lb]
newNodes :: forall lb. Label lb => lb -> [lb] -> [lb]
newNodes lb
dn [lb]
existnodes =
(lb -> Bool) -> [lb] -> [lb]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (lb -> Bool) -> lb -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (lb -> [lb] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [lb]
existnodes)) ([lb] -> [lb]) -> [lb] -> [lb]
forall a b. (a -> b) -> a -> b
$ ([Char], Word32) -> [lb]
forall lb. Label lb => ([Char], Word32) -> [lb]
trynodes (lb -> ([Char], Word32)
forall lb. Label lb => lb -> ([Char], Word32)
noderootindex lb
dn)
noderootindex :: (Label lb) => lb -> (String, Word32)
noderootindex :: forall lb. Label lb => lb -> ([Char], Word32)
noderootindex lb
dn = ([Char]
nh,Word32
nx)
where
([Char]
nh,[Char]
nt) = [Char] -> ([Char], [Char])
splitnodeid ([Char] -> ([Char], [Char])) -> [Char] -> ([Char], [Char])
forall a b. (a -> b) -> a -> b
$ lb -> [Char]
forall lb. Label lb => lb -> [Char]
getLocal lb
dn
nx :: Word32
nx = if [Char] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Char]
nt then Word32
0 else [Char] -> Word32
forall a. Read a => [Char] -> a
read [Char]
nt
splitnodeid :: String -> (String,String)
splitnodeid :: [Char] -> ([Char], [Char])
splitnodeid = (Char -> Bool) -> [Char] -> ([Char], [Char])
forall a. (a -> Bool) -> [a] -> ([a], [a])
break Char -> Bool
isDigit
trynodes :: (Label lb) => (String, Word32) -> [lb]
trynodes :: forall lb. Label lb => ([Char], Word32) -> [lb]
trynodes ([Char]
nr,Word32
nx) = [ [Char] -> lb
forall lb. Label lb => [Char] -> lb
makeLabel ([Char]
nr [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ Word32 -> [Char]
forall a. Show a => a -> [Char]
show Word32
n) | Word32
n <- (Word32 -> Word32) -> Word32 -> [Word32]
forall a. (a -> a) -> a -> [a]
iterate (Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
+ Word32
1) Word32
nx ]
type RDFGraph = NSGraph RDFLabel
toRDFGraph ::
RDFArcSet
-> RDFGraph
toRDFGraph :: RDFArcSet -> RDFGraph
toRDFGraph RDFArcSet
arcs =
let lbls :: Set RDFLabel
lbls = (RDFTriple -> [RDFLabel]) -> RDFArcSet -> Set RDFLabel
forall b a. Ord b => (a -> [b]) -> Set a -> Set b
getComponents RDFTriple -> [RDFLabel]
forall lb. Arc lb -> [lb]
arcLabels RDFArcSet
arcs
getNS :: RDFLabel -> Maybe ScopedName
getNS (Res ScopedName
s) = ScopedName -> Maybe ScopedName
forall a. a -> Maybe a
Just ScopedName
s
getNS (TypedLit Text
_ ScopedName
dt) = ScopedName -> Maybe ScopedName
forall a. a -> Maybe a
Just ScopedName
dt
getNS RDFLabel
_ = Maybe ScopedName
forall a. Maybe a
Nothing
ns :: [Namespace]
ns = (RDFLabel -> Maybe Namespace) -> [RDFLabel] -> [Namespace]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe ((ScopedName -> Namespace) -> Maybe ScopedName -> Maybe Namespace
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ScopedName -> Namespace
getScopeNamespace (Maybe ScopedName -> Maybe Namespace)
-> (RDFLabel -> Maybe ScopedName) -> RDFLabel -> Maybe Namespace
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RDFLabel -> Maybe ScopedName
getNS) ([RDFLabel] -> [Namespace]) -> [RDFLabel] -> [Namespace]
forall a b. (a -> b) -> a -> b
$ Set RDFLabel -> [RDFLabel]
forall a. Set a -> [a]
S.toList Set RDFLabel
lbls
nsmap :: NamespaceMap
nsmap = (NamespaceMap -> Namespace -> NamespaceMap)
-> NamespaceMap -> [Namespace] -> NamespaceMap
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl'
(\NamespaceMap
m Namespace
ins -> let (Maybe Text
p,URI
u) = Namespace -> (Maybe Text, URI)
getNamespaceTuple Namespace
ins
in (URI -> URI -> URI)
-> Maybe Text -> URI -> NamespaceMap -> NamespaceMap
forall k a. Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
M.insertWith ((URI -> URI) -> URI -> URI -> URI
forall a b. a -> b -> a
const URI -> URI
forall a. a -> a
id) Maybe Text
p URI
u NamespaceMap
m)
NamespaceMap
emptyNamespaceMap [Namespace]
ns
in RDFGraph
forall a. Monoid a => a
mempty { namespaces = nsmap, statements = arcs }
emptyRDFGraph :: RDFGraph
emptyRDFGraph :: RDFGraph
emptyRDFGraph = RDFGraph
forall a. Monoid a => a
mempty