{-# LANGUAGE DeriveGeneric
, DeriveAnyClass
#-}
module Data.RDF.Graph (
GNode(..)
, GEdge
, rdfGraph
, triplesGraph
, graphRDF
, graphTriples
) where
import Control.DeepSeq
import qualified Data.Graph.Inductive.Graph as G
import qualified Data.Graph.Inductive.NodeMap as G
import Data.Maybe
import Data.RDF.Types
import GHC.Generics
data GNode = IRIGNode !IRI
| BlankGNode !BlankNode
| LiteralGNode !Literal
deriving ( GNode -> GNode -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GNode -> GNode -> Bool
$c/= :: GNode -> GNode -> Bool
== :: GNode -> GNode -> Bool
$c== :: GNode -> GNode -> Bool
Eq
, Eq GNode
GNode -> GNode -> Bool
GNode -> GNode -> Ordering
GNode -> GNode -> GNode
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: GNode -> GNode -> GNode
$cmin :: GNode -> GNode -> GNode
max :: GNode -> GNode -> GNode
$cmax :: GNode -> GNode -> GNode
>= :: GNode -> GNode -> Bool
$c>= :: GNode -> GNode -> Bool
> :: GNode -> GNode -> Bool
$c> :: GNode -> GNode -> Bool
<= :: GNode -> GNode -> Bool
$c<= :: GNode -> GNode -> Bool
< :: GNode -> GNode -> Bool
$c< :: GNode -> GNode -> Bool
compare :: GNode -> GNode -> Ordering
$ccompare :: GNode -> GNode -> Ordering
Ord
, ReadPrec [GNode]
ReadPrec GNode
Int -> ReadS GNode
ReadS [GNode]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GNode]
$creadListPrec :: ReadPrec [GNode]
readPrec :: ReadPrec GNode
$creadPrec :: ReadPrec GNode
readList :: ReadS [GNode]
$creadList :: ReadS [GNode]
readsPrec :: Int -> ReadS GNode
$creadsPrec :: Int -> ReadS GNode
Read
, Int -> GNode -> ShowS
[GNode] -> ShowS
GNode -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GNode] -> ShowS
$cshowList :: [GNode] -> ShowS
show :: GNode -> String
$cshow :: GNode -> String
showsPrec :: Int -> GNode -> ShowS
$cshowsPrec :: Int -> GNode -> ShowS
Show
, forall x. Rep GNode x -> GNode
forall x. GNode -> Rep GNode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GNode x -> GNode
$cfrom :: forall x. GNode -> Rep GNode x
Generic
, GNode -> ()
forall a. (a -> ()) -> NFData a
rnf :: GNode -> ()
$crnf :: GNode -> ()
NFData
)
type GEdge = Predicate
subjectNode :: Subject -> GNode
subjectNode :: Subject -> GNode
subjectNode (IRISubject IRI
i) = IRI -> GNode
IRIGNode IRI
i
subjectNode (BlankSubject BlankNode
b) = BlankNode -> GNode
BlankGNode BlankNode
b
objectNode :: Object -> GNode
objectNode :: Object -> GNode
objectNode (IRIObject IRI
i) = IRI -> GNode
IRIGNode IRI
i
objectNode (BlankObject BlankNode
b) = BlankNode -> GNode
BlankGNode BlankNode
b
objectNode (LiteralObject Literal
l) = Literal -> GNode
LiteralGNode Literal
l
nodeSubject :: GNode -> Either String Subject
nodeSubject :: GNode -> Either String Subject
nodeSubject (IRIGNode IRI
i) = forall a b. b -> Either a b
Right (IRI -> Subject
IRISubject IRI
i)
nodeSubject (BlankGNode BlankNode
b) = forall a b. b -> Either a b
Right (BlankNode -> Subject
BlankSubject BlankNode
b)
nodeSubject GNode
_ = forall a b. a -> Either a b
Left String
"nodeSubject: subject must IRI or blank node."
nodeObject :: GNode -> Object
nodeObject :: GNode -> Object
nodeObject (IRIGNode IRI
i) = IRI -> Object
IRIObject IRI
i
nodeObject (BlankGNode BlankNode
b) = BlankNode -> Object
BlankObject BlankNode
b
nodeObject (LiteralGNode Literal
l) = Literal -> Object
LiteralObject Literal
l
rdfGraph :: G.DynGraph g => RDFGraph -> (g GNode GEdge, G.NodeMap GNode)
rdfGraph :: forall (g :: * -> * -> *).
DynGraph g =>
RDFGraph -> (g GNode GEdge, NodeMap GNode)
rdfGraph (RDFGraph Maybe IRI
_ [Triple]
ts) = forall (g :: * -> * -> *).
DynGraph g =>
[Triple] -> (g GNode GEdge, NodeMap GNode)
triplesGraph [Triple]
ts
triplesGraph :: G.DynGraph g => [Triple] -> (g GNode GEdge, G.NodeMap GNode)
triplesGraph :: forall (g :: * -> * -> *).
DynGraph g =>
[Triple] -> (g GNode GEdge, NodeMap GNode)
triplesGraph [Triple]
triples = forall a (g :: * -> * -> *) b.
(Ord a, DynGraph g) =>
[a] -> [(a, a, b)] -> (g a b, NodeMap a)
G.mkMapGraph [GNode]
nodes [(GNode, GNode, GEdge)]
edges
where ([GNode]
nodes, [(GNode, GNode, GEdge)]
edges) = ([GNode], [(GNode, GNode, GEdge)])
-> [Triple] -> ([GNode], [(GNode, GNode, GEdge)])
go ([],[]) [Triple]
triples
go :: ([GNode], [(GNode, GNode, GEdge)])
-> [Triple] -> ([GNode], [(GNode, GNode, GEdge)])
go ([GNode]
ns, [(GNode, GNode, GEdge)]
es) [] = ([GNode]
ns, [(GNode, GNode, GEdge)]
es)
go ([GNode]
ns, [(GNode, GNode, GEdge)]
es) (Triple Subject
s GEdge
p Object
o:[Triple]
ts) = let s' :: GNode
s' = Subject -> GNode
subjectNode Subject
s
o' :: GNode
o' = Object -> GNode
objectNode Object
o
in ([GNode], [(GNode, GNode, GEdge)])
-> [Triple] -> ([GNode], [(GNode, GNode, GEdge)])
go (GNode
s'forall a. a -> [a] -> [a]
:GNode
o'forall a. a -> [a] -> [a]
:[GNode]
ns, (GNode
s', GNode
o', GEdge
p)forall a. a -> [a] -> [a]
:[(GNode, GNode, GEdge)]
es) [Triple]
ts
graphRDF :: G.Graph g => Maybe IRI -> g GNode GEdge -> Either String RDFGraph
graphRDF :: forall (g :: * -> * -> *).
Graph g =>
Maybe IRI -> g GNode GEdge -> Either String RDFGraph
graphRDF Maybe IRI
l = (Maybe IRI -> [Triple] -> RDFGraph
RDFGraph Maybe IRI
l forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (g :: * -> * -> *).
Graph g =>
g GNode GEdge -> Either String [Triple]
graphTriples
graphTriples :: G.Graph g => g GNode GEdge -> Either String [Triple]
graphTriples :: forall (g :: * -> * -> *).
Graph g =>
g GNode GEdge -> Either String [Triple]
graphTriples g GNode GEdge
g = [(Int, Int, GEdge)] -> Either String [Triple]
go (forall (gr :: * -> * -> *) a b. Graph gr => gr a b -> [LEdge b]
G.labEdges g GNode GEdge
g)
where go :: [(Int, Int, GEdge)] -> Either String [Triple]
go [] = forall a b. b -> Either a b
Right []
go ((Int
si, Int
oi, GEdge
p):[(Int, Int, GEdge)]
ts) = let s :: Either String Subject
s = GNode -> Either String Subject
nodeSubject (forall a. HasCallStack => Maybe a -> a
fromJust (forall (gr :: * -> * -> *) a b.
Graph gr =>
gr a b -> Int -> Maybe a
G.lab g GNode GEdge
g Int
si))
o :: Object
o = GNode -> Object
nodeObject (forall a. HasCallStack => Maybe a -> a
fromJust (forall (gr :: * -> * -> *) a b.
Graph gr =>
gr a b -> Int -> Maybe a
G.lab g GNode GEdge
g Int
oi))
in ((\Subject
s' -> (Subject -> GEdge -> Object -> Triple
Triple Subject
s' GEdge
p Object
oforall a. a -> [a] -> [a]
:)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Either String Subject
s) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [(Int, Int, GEdge)] -> Either String [Triple]
go [(Int, Int, GEdge)]
ts