{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE EmptyDataDecls #-}


-- |"TriplesGraph" contains a list-backed graph implementation suitable
-- for smallish graphs or for temporary graphs that will not be queried.
-- It maintains the triples in the order that they are given in, and is
-- especially useful for holding N-Triples, where it is often desirable
-- to preserve the order of the triples when they were originally parsed.
-- Duplicate triples are not filtered. If you might have duplicate triples,
-- use @MGraph@ instead, which is also more efficient. However, the query
-- functions of this graph (select, query) remove duplicates from their
-- result triples (but triplesOf does not) since it is usually cheap
-- to do so.
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.RDF.Namespace
import Data.RDF.Query
import Data.RDF.Types (RDF,Rdf(..),Triple(..),Subject,Predicate,Object,NodeSelector,Triples,BaseUrl)
import Data.List (nub)
import GHC.Generics

-- |A simple implementation of the 'RDF' type class that represents
-- the graph internally as a list of triples.
--
-- Note that this type of RDF is fine for interactive
-- experimentation and querying of smallish (<10,000 triples) graphs,
-- but there are better options for larger graphs or graphs that you
-- will do many queries against (e.g., @MGraph@ is faster for queries).
--
-- The time complexity of the functions (where n == num_triples) are:
--
--  * 'empty'    : O(1)
--
--  * 'mkRdf'  : O(n)
--
--  * 'triplesOf': O(1)
--
--  * 'select'   : O(n)
--
--  * 'query'    : O(n)

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
$cto :: forall x. Rep TList x -> TList
$cfrom :: forall x. TList -> Rep TList x
Generic)

instance Binary TList
instance NFData TList

data 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
$cto :: forall x. Rep (RDF TList) x -> RDF TList
$cfrom :: forall x. RDF TList -> Rep (RDF TList) x
Generic,RDF TList -> ()
(RDF TList -> ()) -> NFData (RDF TList)
forall a. (a -> ()) -> NFData a
rnf :: RDF TList -> ()
$crnf :: 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 Node -> Maybe Node -> Maybe Node -> Triples
query             = RDF TList -> Maybe Node -> Maybe Node -> Maybe Node -> Triples
query'
  showGraph :: RDF TList -> String
showGraph         = RDF TList -> String
showGraph'

showGraph' :: RDF TList -> String
showGraph' :: RDF TList -> String
showGraph' RDF TList
gr = (Triple -> String) -> Triples -> String
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\Triple
t -> Triple -> String
forall a. Show a => a -> String
show Triple
t String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"\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(_, _, pms)) = PrefixMappings
pms

addPrefixMappings' :: RDF TList -> PrefixMappings -> Bool -> RDF TList
addPrefixMappings' :: RDF TList -> PrefixMappings -> Bool -> RDF TList
addPrefixMappings' (TListC(ts, baseURL, 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(_, baseURL, _)) = 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)

-- We no longer remove duplicates here, as it is very time consuming and is often not
-- necessary (raptor does not seem to remove dupes either). Instead, we remove dupes
-- from the results of the select' and query' functions, since it is cheap to do
-- there in most cases, but not when triplesOf' is called.
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 (ts, bURL, preMapping)) Triple
t = (Triples, Maybe BaseUrl, PrefixMappings) -> RDF TList
TListC (Triple
tTriple -> 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 (ts, bURL, 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(ts, _, _))) = 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 Node -> Maybe Node -> Maybe Node -> Triples
query' RDF TList
g Maybe Node
s Maybe Node
p Maybe Node
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 Node -> Maybe Node -> Maybe Node -> Triple -> Bool
matchPattern Maybe Node
s Maybe Node
p Maybe Node
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 Node
s' Node
p' Node
o') = NodeSelector -> Node -> Bool
forall a. Maybe (a -> Bool) -> a -> Bool
match NodeSelector
s Node
s' Bool -> Bool -> Bool
&& NodeSelector -> Node -> Bool
forall a. Maybe (a -> Bool) -> a -> Bool
match NodeSelector
p Node
p' Bool -> Bool -> Bool
&& NodeSelector -> Node -> Bool
forall a. Maybe (a -> Bool) -> a -> Bool
match NodeSelector
o Node
o'
  where match :: Maybe (a -> Bool) -> a -> Bool
match Maybe (a -> Bool)
fn a
n = Bool -> ((a -> Bool) -> Bool) -> Maybe (a -> Bool) -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
True ((a -> Bool) -> a -> Bool
forall a b. (a -> b) -> a -> b
$ a
n) Maybe (a -> Bool)
fn

matchPattern :: Maybe Subject -> Maybe Predicate -> Maybe Object -> Triple -> Bool
matchPattern :: Maybe Node -> Maybe Node -> Maybe Node -> Triple -> Bool
matchPattern Maybe Node
s Maybe Node
p Maybe Node
o (Triple Node
s' Node
p' Node
o') = Maybe Node -> Node -> Bool
forall a. Eq a => Maybe a -> a -> Bool
match Maybe Node
s Node
s' Bool -> Bool -> Bool
&& Maybe Node -> Node -> Bool
forall a. Eq a => Maybe a -> a -> Bool
match Maybe Node
p Node
p' Bool -> Bool -> Bool
&& Maybe Node -> Node -> Bool
forall a. Eq a => Maybe a -> a -> Bool
match Maybe Node
o Node
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