{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeFamilies #-}
module Data.RDF.Graph.TList (TList) where
import Prelude
#if MIN_VERSION_base(4,9,0)
#if !MIN_VERSION_base(4,11,0)
import Data.Semigroup
#else
#endif
#else
#endif
import Control.DeepSeq (NFData)
import Data.Binary
import Data.List (nub)
import Data.RDF.Namespace
import Data.RDF.Query
import Data.RDF.Types (BaseUrl, NodeSelector, Object, Predicate, RDF, Rdf (..), Subject, Triple (..), Triples)
import GHC.Generics
data TList deriving ((forall x. TList -> Rep TList x)
-> (forall x. Rep TList x -> TList) -> Generic TList
forall x. Rep TList x -> TList
forall x. TList -> Rep TList x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TList -> Rep TList x
from :: forall x. TList -> Rep TList x
$cto :: forall x. Rep TList x -> TList
to :: forall x. Rep TList x -> TList
Generic)
instance Binary TList
instance NFData TList
newtype instance RDF TList = TListC (Triples, Maybe BaseUrl, PrefixMappings)
deriving ((forall x. RDF TList -> Rep (RDF TList) x)
-> (forall x. Rep (RDF TList) x -> RDF TList)
-> Generic (RDF TList)
forall x. Rep (RDF TList) x -> RDF TList
forall x. RDF TList -> Rep (RDF TList) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RDF TList -> Rep (RDF TList) x
from :: forall x. RDF TList -> Rep (RDF TList) x
$cto :: forall x. Rep (RDF TList) x -> RDF TList
to :: forall x. Rep (RDF TList) x -> RDF TList
Generic, RDF TList -> ()
(RDF TList -> ()) -> NFData (RDF TList)
forall a. (a -> ()) -> NFData a
$crnf :: RDF TList -> ()
rnf :: RDF TList -> ()
NFData)
instance Rdf TList where
baseUrl :: RDF TList -> Maybe BaseUrl
baseUrl = RDF TList -> Maybe BaseUrl
baseUrl'
prefixMappings :: RDF TList -> PrefixMappings
prefixMappings = RDF TList -> PrefixMappings
prefixMappings'
addPrefixMappings :: RDF TList -> PrefixMappings -> Bool -> RDF TList
addPrefixMappings = RDF TList -> PrefixMappings -> Bool -> RDF TList
addPrefixMappings'
empty :: RDF TList
empty = RDF TList
empty'
mkRdf :: Triples -> Maybe BaseUrl -> PrefixMappings -> RDF TList
mkRdf = Triples -> Maybe BaseUrl -> PrefixMappings -> RDF TList
mkRdf'
addTriple :: RDF TList -> Triple -> RDF TList
addTriple = RDF TList -> Triple -> RDF TList
addTriple'
removeTriple :: RDF TList -> Triple -> RDF TList
removeTriple = RDF TList -> Triple -> RDF TList
removeTriple'
triplesOf :: RDF TList -> Triples
triplesOf = RDF TList -> Triples
triplesOf'
uniqTriplesOf :: RDF TList -> Triples
uniqTriplesOf = RDF TList -> Triples
uniqTriplesOf'
select :: RDF TList
-> NodeSelector -> NodeSelector -> NodeSelector -> Triples
select = RDF TList
-> NodeSelector -> NodeSelector -> NodeSelector -> Triples
select'
query :: RDF TList
-> Maybe Subject -> Maybe Subject -> Maybe Subject -> Triples
query = RDF TList
-> Maybe Subject -> Maybe Subject -> Maybe Subject -> Triples
query'
showGraph :: RDF TList -> [Char]
showGraph = RDF TList -> [Char]
showGraph'
showGraph' :: RDF TList -> String
showGraph' :: RDF TList -> [Char]
showGraph' RDF TList
gr = (Triple -> [Char]) -> Triples -> [Char]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\Triple
t -> Triple -> [Char]
forall a. Show a => a -> [Char]
show Triple
t [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> [Char]
"\n") (RDF TList -> Triples
forall a. Rdf a => RDF a -> Triples
expandTriples RDF TList
gr)
prefixMappings' :: RDF TList -> PrefixMappings
prefixMappings' :: RDF TList -> PrefixMappings
prefixMappings' (TListC (Triples
_, Maybe BaseUrl
_, PrefixMappings
pms)) = PrefixMappings
pms
addPrefixMappings' :: RDF TList -> PrefixMappings -> Bool -> RDF TList
addPrefixMappings' :: RDF TList -> PrefixMappings -> Bool -> RDF TList
addPrefixMappings' (TListC (Triples
ts, Maybe BaseUrl
baseURL, PrefixMappings
pms)) PrefixMappings
pms' Bool
replace =
let merge :: PrefixMappings -> PrefixMappings -> PrefixMappings
merge = if Bool
replace then (PrefixMappings -> PrefixMappings -> PrefixMappings)
-> PrefixMappings -> PrefixMappings -> PrefixMappings
forall a b c. (a -> b -> c) -> b -> a -> c
flip PrefixMappings -> PrefixMappings -> PrefixMappings
forall a. Semigroup a => a -> a -> a
(<>) else PrefixMappings -> PrefixMappings -> PrefixMappings
forall a. Semigroup a => a -> a -> a
(<>)
in (Triples, Maybe BaseUrl, PrefixMappings) -> RDF TList
TListC (Triples
ts, Maybe BaseUrl
baseURL, PrefixMappings -> PrefixMappings -> PrefixMappings
merge PrefixMappings
pms PrefixMappings
pms')
baseUrl' :: RDF TList -> Maybe BaseUrl
baseUrl' :: RDF TList -> Maybe BaseUrl
baseUrl' (TListC (Triples
_, Maybe BaseUrl
baseURL, PrefixMappings
_)) = Maybe BaseUrl
baseURL
empty' :: RDF TList
empty' :: RDF TList
empty' = (Triples, Maybe BaseUrl, PrefixMappings) -> RDF TList
TListC (Triples
forall a. Monoid a => a
mempty, Maybe BaseUrl
forall a. Maybe a
Nothing, Map Text Text -> PrefixMappings
PrefixMappings Map Text Text
forall a. Monoid a => a
mempty)
mkRdf' :: Triples -> Maybe BaseUrl -> PrefixMappings -> RDF TList
mkRdf' :: Triples -> Maybe BaseUrl -> PrefixMappings -> RDF TList
mkRdf' Triples
ts Maybe BaseUrl
baseURL PrefixMappings
pms = (Triples, Maybe BaseUrl, PrefixMappings) -> RDF TList
TListC (Triples
ts, Maybe BaseUrl
baseURL, PrefixMappings
pms)
addTriple' :: RDF TList -> Triple -> RDF TList
addTriple' :: RDF TList -> Triple -> RDF TList
addTriple' (TListC (Triples
ts, Maybe BaseUrl
bURL, PrefixMappings
preMapping)) Triple
t = (Triples, Maybe BaseUrl, PrefixMappings) -> RDF TList
TListC (Triple
t Triple -> Triples -> Triples
forall a. a -> [a] -> [a]
: Triples
ts, Maybe BaseUrl
bURL, PrefixMappings
preMapping)
removeTriple' :: RDF TList -> Triple -> RDF TList
removeTriple' :: RDF TList -> Triple -> RDF TList
removeTriple' (TListC (Triples
ts, Maybe BaseUrl
bURL, PrefixMappings
preMapping)) Triple
t = (Triples, Maybe BaseUrl, PrefixMappings) -> RDF TList
TListC (Triples
newTs, Maybe BaseUrl
bURL, PrefixMappings
preMapping)
where
newTs :: Triples
newTs = (Triple -> Bool) -> Triples -> Triples
forall a. (a -> Bool) -> [a] -> [a]
filter (Triple -> Triple -> Bool
forall a. Eq a => a -> a -> Bool
/= Triple
t) Triples
ts
triplesOf' :: RDF TList -> Triples
triplesOf' :: RDF TList -> Triples
triplesOf' ((TListC (Triples
ts, Maybe BaseUrl
_, PrefixMappings
_))) = Triples
ts
uniqTriplesOf' :: RDF TList -> Triples
uniqTriplesOf' :: RDF TList -> Triples
uniqTriplesOf' = Triples -> Triples
forall a. Eq a => [a] -> [a]
nub (Triples -> Triples)
-> (RDF TList -> Triples) -> RDF TList -> Triples
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RDF TList -> Triples
forall a. Rdf a => RDF a -> Triples
expandTriples
select' :: RDF TList -> NodeSelector -> NodeSelector -> NodeSelector -> Triples
select' :: RDF TList
-> NodeSelector -> NodeSelector -> NodeSelector -> Triples
select' RDF TList
g NodeSelector
s NodeSelector
p NodeSelector
o = Triples -> Triples
forall a. Eq a => [a] -> [a]
nub (Triples -> Triples) -> Triples -> Triples
forall a b. (a -> b) -> a -> b
$ (Triple -> Bool) -> Triples -> Triples
forall a. (a -> Bool) -> [a] -> [a]
filter (NodeSelector -> NodeSelector -> NodeSelector -> Triple -> Bool
matchSelect NodeSelector
s NodeSelector
p NodeSelector
o) (Triples -> Triples) -> Triples -> Triples
forall a b. (a -> b) -> a -> b
$ RDF TList -> Triples
forall a. Rdf a => RDF a -> Triples
triplesOf RDF TList
g
query' :: RDF TList -> Maybe Subject -> Maybe Predicate -> Maybe Object -> Triples
query' :: RDF TList
-> Maybe Subject -> Maybe Subject -> Maybe Subject -> Triples
query' RDF TList
g Maybe Subject
s Maybe Subject
p Maybe Subject
o = Triples -> Triples
forall a. Eq a => [a] -> [a]
nub (Triples -> Triples) -> Triples -> Triples
forall a b. (a -> b) -> a -> b
$ (Triple -> Bool) -> Triples -> Triples
forall a. (a -> Bool) -> [a] -> [a]
filter (Maybe Subject -> Maybe Subject -> Maybe Subject -> Triple -> Bool
matchPattern Maybe Subject
s Maybe Subject
p Maybe Subject
o) (Triples -> Triples) -> Triples -> Triples
forall a b. (a -> b) -> a -> b
$ RDF TList -> Triples
forall a. Rdf a => RDF a -> Triples
triplesOf RDF TList
g
matchSelect :: NodeSelector -> NodeSelector -> NodeSelector -> Triple -> Bool
matchSelect :: NodeSelector -> NodeSelector -> NodeSelector -> Triple -> Bool
matchSelect NodeSelector
s NodeSelector
p NodeSelector
o (Triple Subject
s' Subject
p' Subject
o') = NodeSelector -> Subject -> Bool
forall {p}. Maybe (p -> Bool) -> p -> Bool
match NodeSelector
s Subject
s' Bool -> Bool -> Bool
&& NodeSelector -> Subject -> Bool
forall {p}. Maybe (p -> Bool) -> p -> Bool
match NodeSelector
p Subject
p' Bool -> Bool -> Bool
&& NodeSelector -> Subject -> Bool
forall {p}. Maybe (p -> Bool) -> p -> Bool
match NodeSelector
o Subject
o'
where
match :: Maybe (p -> Bool) -> p -> Bool
match Maybe (p -> Bool)
fn p
n = Bool -> ((p -> Bool) -> Bool) -> Maybe (p -> Bool) -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
True ((p -> Bool) -> p -> Bool
forall a b. (a -> b) -> a -> b
$ p
n) Maybe (p -> Bool)
fn
matchPattern :: Maybe Subject -> Maybe Predicate -> Maybe Object -> Triple -> Bool
matchPattern :: Maybe Subject -> Maybe Subject -> Maybe Subject -> Triple -> Bool
matchPattern Maybe Subject
s Maybe Subject
p Maybe Subject
o (Triple Subject
s' Subject
p' Subject
o') = Maybe Subject -> Subject -> Bool
forall {a}. Eq a => Maybe a -> a -> Bool
match Maybe Subject
s Subject
s' Bool -> Bool -> Bool
&& Maybe Subject -> Subject -> Bool
forall {a}. Eq a => Maybe a -> a -> Bool
match Maybe Subject
p Subject
p' Bool -> Bool -> Bool
&& Maybe Subject -> Subject -> Bool
forall {a}. Eq a => Maybe a -> a -> Bool
match Maybe Subject
o Subject
o'
where
match :: Maybe a -> a -> Bool
match Maybe a
n1 a
n2 = Bool -> (a -> Bool) -> Maybe a -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
True (a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
n2) Maybe a
n1