{-# LANGUAGE DeriveGeneric
, DeriveAnyClass
, OverloadedStrings
#-}
module Data.RDF.Internal where
import Control.Applicative
import Control.DeepSeq
import qualified Data.Attoparsec.Combinator as A
import qualified Data.Attoparsec.Text as A
import Data.Char
import Data.String
import GHC.Generics
import qualified Data.Text as T
data RDFGraph = RDFGraph {
RDFGraph -> Maybe IRI
rdfLabel :: !(Maybe IRI)
, RDFGraph -> [Triple]
rdfTriples :: [Triple]
} deriving ( RDFGraph -> RDFGraph -> Bool
(RDFGraph -> RDFGraph -> Bool)
-> (RDFGraph -> RDFGraph -> Bool) -> Eq RDFGraph
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RDFGraph -> RDFGraph -> Bool
$c/= :: RDFGraph -> RDFGraph -> Bool
== :: RDFGraph -> RDFGraph -> Bool
$c== :: RDFGraph -> RDFGraph -> Bool
Eq
, Eq RDFGraph
Eq RDFGraph
-> (RDFGraph -> RDFGraph -> Ordering)
-> (RDFGraph -> RDFGraph -> Bool)
-> (RDFGraph -> RDFGraph -> Bool)
-> (RDFGraph -> RDFGraph -> Bool)
-> (RDFGraph -> RDFGraph -> Bool)
-> (RDFGraph -> RDFGraph -> RDFGraph)
-> (RDFGraph -> RDFGraph -> RDFGraph)
-> Ord RDFGraph
RDFGraph -> RDFGraph -> Bool
RDFGraph -> RDFGraph -> Ordering
RDFGraph -> RDFGraph -> RDFGraph
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 :: RDFGraph -> RDFGraph -> RDFGraph
$cmin :: RDFGraph -> RDFGraph -> RDFGraph
max :: RDFGraph -> RDFGraph -> RDFGraph
$cmax :: RDFGraph -> RDFGraph -> RDFGraph
>= :: RDFGraph -> RDFGraph -> Bool
$c>= :: RDFGraph -> RDFGraph -> Bool
> :: RDFGraph -> RDFGraph -> Bool
$c> :: RDFGraph -> RDFGraph -> Bool
<= :: RDFGraph -> RDFGraph -> Bool
$c<= :: RDFGraph -> RDFGraph -> Bool
< :: RDFGraph -> RDFGraph -> Bool
$c< :: RDFGraph -> RDFGraph -> Bool
compare :: RDFGraph -> RDFGraph -> Ordering
$ccompare :: RDFGraph -> RDFGraph -> Ordering
$cp1Ord :: Eq RDFGraph
Ord
, ReadPrec [RDFGraph]
ReadPrec RDFGraph
Int -> ReadS RDFGraph
ReadS [RDFGraph]
(Int -> ReadS RDFGraph)
-> ReadS [RDFGraph]
-> ReadPrec RDFGraph
-> ReadPrec [RDFGraph]
-> Read RDFGraph
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RDFGraph]
$creadListPrec :: ReadPrec [RDFGraph]
readPrec :: ReadPrec RDFGraph
$creadPrec :: ReadPrec RDFGraph
readList :: ReadS [RDFGraph]
$creadList :: ReadS [RDFGraph]
readsPrec :: Int -> ReadS RDFGraph
$creadsPrec :: Int -> ReadS RDFGraph
Read
, Int -> RDFGraph -> ShowS
[RDFGraph] -> ShowS
RDFGraph -> String
(Int -> RDFGraph -> ShowS)
-> (RDFGraph -> String) -> ([RDFGraph] -> ShowS) -> Show RDFGraph
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RDFGraph] -> ShowS
$cshowList :: [RDFGraph] -> ShowS
show :: RDFGraph -> String
$cshow :: RDFGraph -> String
showsPrec :: Int -> RDFGraph -> ShowS
$cshowsPrec :: Int -> RDFGraph -> ShowS
Show
, (forall x. RDFGraph -> Rep RDFGraph x)
-> (forall x. Rep RDFGraph x -> RDFGraph) -> Generic RDFGraph
forall x. Rep RDFGraph x -> RDFGraph
forall x. RDFGraph -> Rep RDFGraph x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RDFGraph x -> RDFGraph
$cfrom :: forall x. RDFGraph -> Rep RDFGraph x
Generic
, RDFGraph -> ()
(RDFGraph -> ()) -> NFData RDFGraph
forall a. (a -> ()) -> NFData a
rnf :: RDFGraph -> ()
$crnf :: RDFGraph -> ()
NFData
)
data Quad = Quad {
Quad -> Triple
quadTriple :: !Triple
, Quad -> Maybe IRI
quadGraph :: !(Maybe IRI)
} deriving ( Quad -> Quad -> Bool
(Quad -> Quad -> Bool) -> (Quad -> Quad -> Bool) -> Eq Quad
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Quad -> Quad -> Bool
$c/= :: Quad -> Quad -> Bool
== :: Quad -> Quad -> Bool
$c== :: Quad -> Quad -> Bool
Eq
, Eq Quad
Eq Quad
-> (Quad -> Quad -> Ordering)
-> (Quad -> Quad -> Bool)
-> (Quad -> Quad -> Bool)
-> (Quad -> Quad -> Bool)
-> (Quad -> Quad -> Bool)
-> (Quad -> Quad -> Quad)
-> (Quad -> Quad -> Quad)
-> Ord Quad
Quad -> Quad -> Bool
Quad -> Quad -> Ordering
Quad -> Quad -> Quad
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 :: Quad -> Quad -> Quad
$cmin :: Quad -> Quad -> Quad
max :: Quad -> Quad -> Quad
$cmax :: Quad -> Quad -> Quad
>= :: Quad -> Quad -> Bool
$c>= :: Quad -> Quad -> Bool
> :: Quad -> Quad -> Bool
$c> :: Quad -> Quad -> Bool
<= :: Quad -> Quad -> Bool
$c<= :: Quad -> Quad -> Bool
< :: Quad -> Quad -> Bool
$c< :: Quad -> Quad -> Bool
compare :: Quad -> Quad -> Ordering
$ccompare :: Quad -> Quad -> Ordering
$cp1Ord :: Eq Quad
Ord
, ReadPrec [Quad]
ReadPrec Quad
Int -> ReadS Quad
ReadS [Quad]
(Int -> ReadS Quad)
-> ReadS [Quad] -> ReadPrec Quad -> ReadPrec [Quad] -> Read Quad
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Quad]
$creadListPrec :: ReadPrec [Quad]
readPrec :: ReadPrec Quad
$creadPrec :: ReadPrec Quad
readList :: ReadS [Quad]
$creadList :: ReadS [Quad]
readsPrec :: Int -> ReadS Quad
$creadsPrec :: Int -> ReadS Quad
Read
, Int -> Quad -> ShowS
[Quad] -> ShowS
Quad -> String
(Int -> Quad -> ShowS)
-> (Quad -> String) -> ([Quad] -> ShowS) -> Show Quad
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Quad] -> ShowS
$cshowList :: [Quad] -> ShowS
show :: Quad -> String
$cshow :: Quad -> String
showsPrec :: Int -> Quad -> ShowS
$cshowsPrec :: Int -> Quad -> ShowS
Show
, (forall x. Quad -> Rep Quad x)
-> (forall x. Rep Quad x -> Quad) -> Generic Quad
forall x. Rep Quad x -> Quad
forall x. Quad -> Rep Quad x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Quad x -> Quad
$cfrom :: forall x. Quad -> Rep Quad x
Generic
, Quad -> ()
(Quad -> ()) -> NFData Quad
forall a. (a -> ()) -> NFData a
rnf :: Quad -> ()
$crnf :: Quad -> ()
NFData
)
data Triple = Triple !Subject !Predicate !Object
deriving ( Triple -> Triple -> Bool
(Triple -> Triple -> Bool)
-> (Triple -> Triple -> Bool) -> Eq Triple
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Triple -> Triple -> Bool
$c/= :: Triple -> Triple -> Bool
== :: Triple -> Triple -> Bool
$c== :: Triple -> Triple -> Bool
Eq
, Eq Triple
Eq Triple
-> (Triple -> Triple -> Ordering)
-> (Triple -> Triple -> Bool)
-> (Triple -> Triple -> Bool)
-> (Triple -> Triple -> Bool)
-> (Triple -> Triple -> Bool)
-> (Triple -> Triple -> Triple)
-> (Triple -> Triple -> Triple)
-> Ord Triple
Triple -> Triple -> Bool
Triple -> Triple -> Ordering
Triple -> Triple -> Triple
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 :: Triple -> Triple -> Triple
$cmin :: Triple -> Triple -> Triple
max :: Triple -> Triple -> Triple
$cmax :: Triple -> Triple -> Triple
>= :: Triple -> Triple -> Bool
$c>= :: Triple -> Triple -> Bool
> :: Triple -> Triple -> Bool
$c> :: Triple -> Triple -> Bool
<= :: Triple -> Triple -> Bool
$c<= :: Triple -> Triple -> Bool
< :: Triple -> Triple -> Bool
$c< :: Triple -> Triple -> Bool
compare :: Triple -> Triple -> Ordering
$ccompare :: Triple -> Triple -> Ordering
$cp1Ord :: Eq Triple
Ord
, ReadPrec [Triple]
ReadPrec Triple
Int -> ReadS Triple
ReadS [Triple]
(Int -> ReadS Triple)
-> ReadS [Triple]
-> ReadPrec Triple
-> ReadPrec [Triple]
-> Read Triple
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Triple]
$creadListPrec :: ReadPrec [Triple]
readPrec :: ReadPrec Triple
$creadPrec :: ReadPrec Triple
readList :: ReadS [Triple]
$creadList :: ReadS [Triple]
readsPrec :: Int -> ReadS Triple
$creadsPrec :: Int -> ReadS Triple
Read
, Int -> Triple -> ShowS
[Triple] -> ShowS
Triple -> String
(Int -> Triple -> ShowS)
-> (Triple -> String) -> ([Triple] -> ShowS) -> Show Triple
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Triple] -> ShowS
$cshowList :: [Triple] -> ShowS
show :: Triple -> String
$cshow :: Triple -> String
showsPrec :: Int -> Triple -> ShowS
$cshowsPrec :: Int -> Triple -> ShowS
Show
, (forall x. Triple -> Rep Triple x)
-> (forall x. Rep Triple x -> Triple) -> Generic Triple
forall x. Rep Triple x -> Triple
forall x. Triple -> Rep Triple x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Triple x -> Triple
$cfrom :: forall x. Triple -> Rep Triple x
Generic
, Triple -> ()
(Triple -> ()) -> NFData Triple
forall a. (a -> ()) -> NFData a
rnf :: Triple -> ()
$crnf :: Triple -> ()
NFData
)
data Subject = IRISubject !IRI
| BlankSubject !BlankNode
deriving ( Subject -> Subject -> Bool
(Subject -> Subject -> Bool)
-> (Subject -> Subject -> Bool) -> Eq Subject
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Subject -> Subject -> Bool
$c/= :: Subject -> Subject -> Bool
== :: Subject -> Subject -> Bool
$c== :: Subject -> Subject -> Bool
Eq
, Eq Subject
Eq Subject
-> (Subject -> Subject -> Ordering)
-> (Subject -> Subject -> Bool)
-> (Subject -> Subject -> Bool)
-> (Subject -> Subject -> Bool)
-> (Subject -> Subject -> Bool)
-> (Subject -> Subject -> Subject)
-> (Subject -> Subject -> Subject)
-> Ord Subject
Subject -> Subject -> Bool
Subject -> Subject -> Ordering
Subject -> Subject -> Subject
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 :: Subject -> Subject -> Subject
$cmin :: Subject -> Subject -> Subject
max :: Subject -> Subject -> Subject
$cmax :: Subject -> Subject -> Subject
>= :: Subject -> Subject -> Bool
$c>= :: Subject -> Subject -> Bool
> :: Subject -> Subject -> Bool
$c> :: Subject -> Subject -> Bool
<= :: Subject -> Subject -> Bool
$c<= :: Subject -> Subject -> Bool
< :: Subject -> Subject -> Bool
$c< :: Subject -> Subject -> Bool
compare :: Subject -> Subject -> Ordering
$ccompare :: Subject -> Subject -> Ordering
$cp1Ord :: Eq Subject
Ord
, ReadPrec [Subject]
ReadPrec Subject
Int -> ReadS Subject
ReadS [Subject]
(Int -> ReadS Subject)
-> ReadS [Subject]
-> ReadPrec Subject
-> ReadPrec [Subject]
-> Read Subject
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Subject]
$creadListPrec :: ReadPrec [Subject]
readPrec :: ReadPrec Subject
$creadPrec :: ReadPrec Subject
readList :: ReadS [Subject]
$creadList :: ReadS [Subject]
readsPrec :: Int -> ReadS Subject
$creadsPrec :: Int -> ReadS Subject
Read
, Int -> Subject -> ShowS
[Subject] -> ShowS
Subject -> String
(Int -> Subject -> ShowS)
-> (Subject -> String) -> ([Subject] -> ShowS) -> Show Subject
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Subject] -> ShowS
$cshowList :: [Subject] -> ShowS
show :: Subject -> String
$cshow :: Subject -> String
showsPrec :: Int -> Subject -> ShowS
$cshowsPrec :: Int -> Subject -> ShowS
Show
, (forall x. Subject -> Rep Subject x)
-> (forall x. Rep Subject x -> Subject) -> Generic Subject
forall x. Rep Subject x -> Subject
forall x. Subject -> Rep Subject x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Subject x -> Subject
$cfrom :: forall x. Subject -> Rep Subject x
Generic
, Subject -> ()
(Subject -> ()) -> NFData Subject
forall a. (a -> ()) -> NFData a
rnf :: Subject -> ()
$crnf :: Subject -> ()
NFData
)
newtype Predicate = Predicate { Predicate -> IRI
unPredicate :: IRI }
deriving ( Predicate -> Predicate -> Bool
(Predicate -> Predicate -> Bool)
-> (Predicate -> Predicate -> Bool) -> Eq Predicate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Predicate -> Predicate -> Bool
$c/= :: Predicate -> Predicate -> Bool
== :: Predicate -> Predicate -> Bool
$c== :: Predicate -> Predicate -> Bool
Eq
, Eq Predicate
Eq Predicate
-> (Predicate -> Predicate -> Ordering)
-> (Predicate -> Predicate -> Bool)
-> (Predicate -> Predicate -> Bool)
-> (Predicate -> Predicate -> Bool)
-> (Predicate -> Predicate -> Bool)
-> (Predicate -> Predicate -> Predicate)
-> (Predicate -> Predicate -> Predicate)
-> Ord Predicate
Predicate -> Predicate -> Bool
Predicate -> Predicate -> Ordering
Predicate -> Predicate -> Predicate
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 :: Predicate -> Predicate -> Predicate
$cmin :: Predicate -> Predicate -> Predicate
max :: Predicate -> Predicate -> Predicate
$cmax :: Predicate -> Predicate -> Predicate
>= :: Predicate -> Predicate -> Bool
$c>= :: Predicate -> Predicate -> Bool
> :: Predicate -> Predicate -> Bool
$c> :: Predicate -> Predicate -> Bool
<= :: Predicate -> Predicate -> Bool
$c<= :: Predicate -> Predicate -> Bool
< :: Predicate -> Predicate -> Bool
$c< :: Predicate -> Predicate -> Bool
compare :: Predicate -> Predicate -> Ordering
$ccompare :: Predicate -> Predicate -> Ordering
$cp1Ord :: Eq Predicate
Ord
, ReadPrec [Predicate]
ReadPrec Predicate
Int -> ReadS Predicate
ReadS [Predicate]
(Int -> ReadS Predicate)
-> ReadS [Predicate]
-> ReadPrec Predicate
-> ReadPrec [Predicate]
-> Read Predicate
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Predicate]
$creadListPrec :: ReadPrec [Predicate]
readPrec :: ReadPrec Predicate
$creadPrec :: ReadPrec Predicate
readList :: ReadS [Predicate]
$creadList :: ReadS [Predicate]
readsPrec :: Int -> ReadS Predicate
$creadsPrec :: Int -> ReadS Predicate
Read
, Int -> Predicate -> ShowS
[Predicate] -> ShowS
Predicate -> String
(Int -> Predicate -> ShowS)
-> (Predicate -> String)
-> ([Predicate] -> ShowS)
-> Show Predicate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Predicate] -> ShowS
$cshowList :: [Predicate] -> ShowS
show :: Predicate -> String
$cshow :: Predicate -> String
showsPrec :: Int -> Predicate -> ShowS
$cshowsPrec :: Int -> Predicate -> ShowS
Show
, (forall x. Predicate -> Rep Predicate x)
-> (forall x. Rep Predicate x -> Predicate) -> Generic Predicate
forall x. Rep Predicate x -> Predicate
forall x. Predicate -> Rep Predicate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Predicate x -> Predicate
$cfrom :: forall x. Predicate -> Rep Predicate x
Generic
, Predicate -> ()
(Predicate -> ()) -> NFData Predicate
forall a. (a -> ()) -> NFData a
rnf :: Predicate -> ()
$crnf :: Predicate -> ()
NFData
)
data Object = IRIObject !IRI
| BlankObject !BlankNode
| LiteralObject !Literal
deriving ( Object -> Object -> Bool
(Object -> Object -> Bool)
-> (Object -> Object -> Bool) -> Eq Object
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Object -> Object -> Bool
$c/= :: Object -> Object -> Bool
== :: Object -> Object -> Bool
$c== :: Object -> Object -> Bool
Eq
, Eq Object
Eq Object
-> (Object -> Object -> Ordering)
-> (Object -> Object -> Bool)
-> (Object -> Object -> Bool)
-> (Object -> Object -> Bool)
-> (Object -> Object -> Bool)
-> (Object -> Object -> Object)
-> (Object -> Object -> Object)
-> Ord Object
Object -> Object -> Bool
Object -> Object -> Ordering
Object -> Object -> Object
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 :: Object -> Object -> Object
$cmin :: Object -> Object -> Object
max :: Object -> Object -> Object
$cmax :: Object -> Object -> Object
>= :: Object -> Object -> Bool
$c>= :: Object -> Object -> Bool
> :: Object -> Object -> Bool
$c> :: Object -> Object -> Bool
<= :: Object -> Object -> Bool
$c<= :: Object -> Object -> Bool
< :: Object -> Object -> Bool
$c< :: Object -> Object -> Bool
compare :: Object -> Object -> Ordering
$ccompare :: Object -> Object -> Ordering
$cp1Ord :: Eq Object
Ord
, ReadPrec [Object]
ReadPrec Object
Int -> ReadS Object
ReadS [Object]
(Int -> ReadS Object)
-> ReadS [Object]
-> ReadPrec Object
-> ReadPrec [Object]
-> Read Object
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Object]
$creadListPrec :: ReadPrec [Object]
readPrec :: ReadPrec Object
$creadPrec :: ReadPrec Object
readList :: ReadS [Object]
$creadList :: ReadS [Object]
readsPrec :: Int -> ReadS Object
$creadsPrec :: Int -> ReadS Object
Read
, Int -> Object -> ShowS
[Object] -> ShowS
Object -> String
(Int -> Object -> ShowS)
-> (Object -> String) -> ([Object] -> ShowS) -> Show Object
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Object] -> ShowS
$cshowList :: [Object] -> ShowS
show :: Object -> String
$cshow :: Object -> String
showsPrec :: Int -> Object -> ShowS
$cshowsPrec :: Int -> Object -> ShowS
Show
, (forall x. Object -> Rep Object x)
-> (forall x. Rep Object x -> Object) -> Generic Object
forall x. Rep Object x -> Object
forall x. Object -> Rep Object x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Object x -> Object
$cfrom :: forall x. Object -> Rep Object x
Generic
, Object -> ()
(Object -> ()) -> NFData Object
forall a. (a -> ()) -> NFData a
rnf :: Object -> ()
$crnf :: Object -> ()
NFData
)
newtype BlankNode = BlankNode { BlankNode -> Text
unBlankNode :: T.Text }
deriving ( BlankNode -> BlankNode -> Bool
(BlankNode -> BlankNode -> Bool)
-> (BlankNode -> BlankNode -> Bool) -> Eq BlankNode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BlankNode -> BlankNode -> Bool
$c/= :: BlankNode -> BlankNode -> Bool
== :: BlankNode -> BlankNode -> Bool
$c== :: BlankNode -> BlankNode -> Bool
Eq
, Eq BlankNode
Eq BlankNode
-> (BlankNode -> BlankNode -> Ordering)
-> (BlankNode -> BlankNode -> Bool)
-> (BlankNode -> BlankNode -> Bool)
-> (BlankNode -> BlankNode -> Bool)
-> (BlankNode -> BlankNode -> Bool)
-> (BlankNode -> BlankNode -> BlankNode)
-> (BlankNode -> BlankNode -> BlankNode)
-> Ord BlankNode
BlankNode -> BlankNode -> Bool
BlankNode -> BlankNode -> Ordering
BlankNode -> BlankNode -> BlankNode
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 :: BlankNode -> BlankNode -> BlankNode
$cmin :: BlankNode -> BlankNode -> BlankNode
max :: BlankNode -> BlankNode -> BlankNode
$cmax :: BlankNode -> BlankNode -> BlankNode
>= :: BlankNode -> BlankNode -> Bool
$c>= :: BlankNode -> BlankNode -> Bool
> :: BlankNode -> BlankNode -> Bool
$c> :: BlankNode -> BlankNode -> Bool
<= :: BlankNode -> BlankNode -> Bool
$c<= :: BlankNode -> BlankNode -> Bool
< :: BlankNode -> BlankNode -> Bool
$c< :: BlankNode -> BlankNode -> Bool
compare :: BlankNode -> BlankNode -> Ordering
$ccompare :: BlankNode -> BlankNode -> Ordering
$cp1Ord :: Eq BlankNode
Ord
, ReadPrec [BlankNode]
ReadPrec BlankNode
Int -> ReadS BlankNode
ReadS [BlankNode]
(Int -> ReadS BlankNode)
-> ReadS [BlankNode]
-> ReadPrec BlankNode
-> ReadPrec [BlankNode]
-> Read BlankNode
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BlankNode]
$creadListPrec :: ReadPrec [BlankNode]
readPrec :: ReadPrec BlankNode
$creadPrec :: ReadPrec BlankNode
readList :: ReadS [BlankNode]
$creadList :: ReadS [BlankNode]
readsPrec :: Int -> ReadS BlankNode
$creadsPrec :: Int -> ReadS BlankNode
Read
, Int -> BlankNode -> ShowS
[BlankNode] -> ShowS
BlankNode -> String
(Int -> BlankNode -> ShowS)
-> (BlankNode -> String)
-> ([BlankNode] -> ShowS)
-> Show BlankNode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BlankNode] -> ShowS
$cshowList :: [BlankNode] -> ShowS
show :: BlankNode -> String
$cshow :: BlankNode -> String
showsPrec :: Int -> BlankNode -> ShowS
$cshowsPrec :: Int -> BlankNode -> ShowS
Show
, (forall x. BlankNode -> Rep BlankNode x)
-> (forall x. Rep BlankNode x -> BlankNode) -> Generic BlankNode
forall x. Rep BlankNode x -> BlankNode
forall x. BlankNode -> Rep BlankNode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BlankNode x -> BlankNode
$cfrom :: forall x. BlankNode -> Rep BlankNode x
Generic
, BlankNode -> ()
(BlankNode -> ()) -> NFData BlankNode
forall a. (a -> ()) -> NFData a
rnf :: BlankNode -> ()
$crnf :: BlankNode -> ()
NFData
)
data Literal = Literal {
Literal -> Text
litString :: !T.Text
, Literal -> LiteralType
litType :: !LiteralType
} deriving ( Literal -> Literal -> Bool
(Literal -> Literal -> Bool)
-> (Literal -> Literal -> Bool) -> Eq Literal
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Literal -> Literal -> Bool
$c/= :: Literal -> Literal -> Bool
== :: Literal -> Literal -> Bool
$c== :: Literal -> Literal -> Bool
Eq
, Eq Literal
Eq Literal
-> (Literal -> Literal -> Ordering)
-> (Literal -> Literal -> Bool)
-> (Literal -> Literal -> Bool)
-> (Literal -> Literal -> Bool)
-> (Literal -> Literal -> Bool)
-> (Literal -> Literal -> Literal)
-> (Literal -> Literal -> Literal)
-> Ord Literal
Literal -> Literal -> Bool
Literal -> Literal -> Ordering
Literal -> Literal -> Literal
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 :: Literal -> Literal -> Literal
$cmin :: Literal -> Literal -> Literal
max :: Literal -> Literal -> Literal
$cmax :: Literal -> Literal -> Literal
>= :: Literal -> Literal -> Bool
$c>= :: Literal -> Literal -> Bool
> :: Literal -> Literal -> Bool
$c> :: Literal -> Literal -> Bool
<= :: Literal -> Literal -> Bool
$c<= :: Literal -> Literal -> Bool
< :: Literal -> Literal -> Bool
$c< :: Literal -> Literal -> Bool
compare :: Literal -> Literal -> Ordering
$ccompare :: Literal -> Literal -> Ordering
$cp1Ord :: Eq Literal
Ord
, ReadPrec [Literal]
ReadPrec Literal
Int -> ReadS Literal
ReadS [Literal]
(Int -> ReadS Literal)
-> ReadS [Literal]
-> ReadPrec Literal
-> ReadPrec [Literal]
-> Read Literal
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Literal]
$creadListPrec :: ReadPrec [Literal]
readPrec :: ReadPrec Literal
$creadPrec :: ReadPrec Literal
readList :: ReadS [Literal]
$creadList :: ReadS [Literal]
readsPrec :: Int -> ReadS Literal
$creadsPrec :: Int -> ReadS Literal
Read
, Int -> Literal -> ShowS
[Literal] -> ShowS
Literal -> String
(Int -> Literal -> ShowS)
-> (Literal -> String) -> ([Literal] -> ShowS) -> Show Literal
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Literal] -> ShowS
$cshowList :: [Literal] -> ShowS
show :: Literal -> String
$cshow :: Literal -> String
showsPrec :: Int -> Literal -> ShowS
$cshowsPrec :: Int -> Literal -> ShowS
Show
, (forall x. Literal -> Rep Literal x)
-> (forall x. Rep Literal x -> Literal) -> Generic Literal
forall x. Rep Literal x -> Literal
forall x. Literal -> Rep Literal x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Literal x -> Literal
$cfrom :: forall x. Literal -> Rep Literal x
Generic
, Literal -> ()
(Literal -> ()) -> NFData Literal
forall a. (a -> ()) -> NFData a
rnf :: Literal -> ()
$crnf :: Literal -> ()
NFData
)
data LiteralType = LiteralIRIType !IRI
| LiteralLangType !T.Text
| LiteralUntyped
deriving ( LiteralType -> LiteralType -> Bool
(LiteralType -> LiteralType -> Bool)
-> (LiteralType -> LiteralType -> Bool) -> Eq LiteralType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LiteralType -> LiteralType -> Bool
$c/= :: LiteralType -> LiteralType -> Bool
== :: LiteralType -> LiteralType -> Bool
$c== :: LiteralType -> LiteralType -> Bool
Eq
, Eq LiteralType
Eq LiteralType
-> (LiteralType -> LiteralType -> Ordering)
-> (LiteralType -> LiteralType -> Bool)
-> (LiteralType -> LiteralType -> Bool)
-> (LiteralType -> LiteralType -> Bool)
-> (LiteralType -> LiteralType -> Bool)
-> (LiteralType -> LiteralType -> LiteralType)
-> (LiteralType -> LiteralType -> LiteralType)
-> Ord LiteralType
LiteralType -> LiteralType -> Bool
LiteralType -> LiteralType -> Ordering
LiteralType -> LiteralType -> LiteralType
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 :: LiteralType -> LiteralType -> LiteralType
$cmin :: LiteralType -> LiteralType -> LiteralType
max :: LiteralType -> LiteralType -> LiteralType
$cmax :: LiteralType -> LiteralType -> LiteralType
>= :: LiteralType -> LiteralType -> Bool
$c>= :: LiteralType -> LiteralType -> Bool
> :: LiteralType -> LiteralType -> Bool
$c> :: LiteralType -> LiteralType -> Bool
<= :: LiteralType -> LiteralType -> Bool
$c<= :: LiteralType -> LiteralType -> Bool
< :: LiteralType -> LiteralType -> Bool
$c< :: LiteralType -> LiteralType -> Bool
compare :: LiteralType -> LiteralType -> Ordering
$ccompare :: LiteralType -> LiteralType -> Ordering
$cp1Ord :: Eq LiteralType
Ord
, ReadPrec [LiteralType]
ReadPrec LiteralType
Int -> ReadS LiteralType
ReadS [LiteralType]
(Int -> ReadS LiteralType)
-> ReadS [LiteralType]
-> ReadPrec LiteralType
-> ReadPrec [LiteralType]
-> Read LiteralType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [LiteralType]
$creadListPrec :: ReadPrec [LiteralType]
readPrec :: ReadPrec LiteralType
$creadPrec :: ReadPrec LiteralType
readList :: ReadS [LiteralType]
$creadList :: ReadS [LiteralType]
readsPrec :: Int -> ReadS LiteralType
$creadsPrec :: Int -> ReadS LiteralType
Read
, Int -> LiteralType -> ShowS
[LiteralType] -> ShowS
LiteralType -> String
(Int -> LiteralType -> ShowS)
-> (LiteralType -> String)
-> ([LiteralType] -> ShowS)
-> Show LiteralType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LiteralType] -> ShowS
$cshowList :: [LiteralType] -> ShowS
show :: LiteralType -> String
$cshow :: LiteralType -> String
showsPrec :: Int -> LiteralType -> ShowS
$cshowsPrec :: Int -> LiteralType -> ShowS
Show
, (forall x. LiteralType -> Rep LiteralType x)
-> (forall x. Rep LiteralType x -> LiteralType)
-> Generic LiteralType
forall x. Rep LiteralType x -> LiteralType
forall x. LiteralType -> Rep LiteralType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LiteralType x -> LiteralType
$cfrom :: forall x. LiteralType -> Rep LiteralType x
Generic
, LiteralType -> ()
(LiteralType -> ()) -> NFData LiteralType
forall a. (a -> ()) -> NFData a
rnf :: LiteralType -> ()
$crnf :: LiteralType -> ()
NFData
)
data IRI = IRI {
IRI -> Text
iriScheme :: !T.Text
, IRI -> Maybe IRIAuth
iriAuth :: !(Maybe IRIAuth)
, IRI -> Text
iriPath :: !T.Text
, IRI -> Maybe Text
iriQuery :: !(Maybe T.Text)
, IRI -> Maybe Text
iriFragment :: !(Maybe T.Text)
} deriving ( IRI -> IRI -> Bool
(IRI -> IRI -> Bool) -> (IRI -> IRI -> Bool) -> Eq IRI
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IRI -> IRI -> Bool
$c/= :: IRI -> IRI -> Bool
== :: IRI -> IRI -> Bool
$c== :: IRI -> IRI -> Bool
Eq
, Eq IRI
Eq IRI
-> (IRI -> IRI -> Ordering)
-> (IRI -> IRI -> Bool)
-> (IRI -> IRI -> Bool)
-> (IRI -> IRI -> Bool)
-> (IRI -> IRI -> Bool)
-> (IRI -> IRI -> IRI)
-> (IRI -> IRI -> IRI)
-> Ord IRI
IRI -> IRI -> Bool
IRI -> IRI -> Ordering
IRI -> IRI -> IRI
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 :: IRI -> IRI -> IRI
$cmin :: IRI -> IRI -> IRI
max :: IRI -> IRI -> IRI
$cmax :: IRI -> IRI -> IRI
>= :: IRI -> IRI -> Bool
$c>= :: IRI -> IRI -> Bool
> :: IRI -> IRI -> Bool
$c> :: IRI -> IRI -> Bool
<= :: IRI -> IRI -> Bool
$c<= :: IRI -> IRI -> Bool
< :: IRI -> IRI -> Bool
$c< :: IRI -> IRI -> Bool
compare :: IRI -> IRI -> Ordering
$ccompare :: IRI -> IRI -> Ordering
$cp1Ord :: Eq IRI
Ord
, ReadPrec [IRI]
ReadPrec IRI
Int -> ReadS IRI
ReadS [IRI]
(Int -> ReadS IRI)
-> ReadS [IRI] -> ReadPrec IRI -> ReadPrec [IRI] -> Read IRI
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [IRI]
$creadListPrec :: ReadPrec [IRI]
readPrec :: ReadPrec IRI
$creadPrec :: ReadPrec IRI
readList :: ReadS [IRI]
$creadList :: ReadS [IRI]
readsPrec :: Int -> ReadS IRI
$creadsPrec :: Int -> ReadS IRI
Read
, Int -> IRI -> ShowS
[IRI] -> ShowS
IRI -> String
(Int -> IRI -> ShowS)
-> (IRI -> String) -> ([IRI] -> ShowS) -> Show IRI
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IRI] -> ShowS
$cshowList :: [IRI] -> ShowS
show :: IRI -> String
$cshow :: IRI -> String
showsPrec :: Int -> IRI -> ShowS
$cshowsPrec :: Int -> IRI -> ShowS
Show
, (forall x. IRI -> Rep IRI x)
-> (forall x. Rep IRI x -> IRI) -> Generic IRI
forall x. Rep IRI x -> IRI
forall x. IRI -> Rep IRI x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep IRI x -> IRI
$cfrom :: forall x. IRI -> Rep IRI x
Generic
, IRI -> ()
(IRI -> ()) -> NFData IRI
forall a. (a -> ()) -> NFData a
rnf :: IRI -> ()
$crnf :: IRI -> ()
NFData
)
data IRIAuth = IRIAuth {
IRIAuth -> Maybe Text
iriUser :: !(Maybe T.Text)
, IRIAuth -> Text
iriHost :: T.Text
, IRIAuth -> Maybe Text
iriPort :: !(Maybe T.Text)
} deriving ( IRIAuth -> IRIAuth -> Bool
(IRIAuth -> IRIAuth -> Bool)
-> (IRIAuth -> IRIAuth -> Bool) -> Eq IRIAuth
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IRIAuth -> IRIAuth -> Bool
$c/= :: IRIAuth -> IRIAuth -> Bool
== :: IRIAuth -> IRIAuth -> Bool
$c== :: IRIAuth -> IRIAuth -> Bool
Eq
, Eq IRIAuth
Eq IRIAuth
-> (IRIAuth -> IRIAuth -> Ordering)
-> (IRIAuth -> IRIAuth -> Bool)
-> (IRIAuth -> IRIAuth -> Bool)
-> (IRIAuth -> IRIAuth -> Bool)
-> (IRIAuth -> IRIAuth -> Bool)
-> (IRIAuth -> IRIAuth -> IRIAuth)
-> (IRIAuth -> IRIAuth -> IRIAuth)
-> Ord IRIAuth
IRIAuth -> IRIAuth -> Bool
IRIAuth -> IRIAuth -> Ordering
IRIAuth -> IRIAuth -> IRIAuth
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 :: IRIAuth -> IRIAuth -> IRIAuth
$cmin :: IRIAuth -> IRIAuth -> IRIAuth
max :: IRIAuth -> IRIAuth -> IRIAuth
$cmax :: IRIAuth -> IRIAuth -> IRIAuth
>= :: IRIAuth -> IRIAuth -> Bool
$c>= :: IRIAuth -> IRIAuth -> Bool
> :: IRIAuth -> IRIAuth -> Bool
$c> :: IRIAuth -> IRIAuth -> Bool
<= :: IRIAuth -> IRIAuth -> Bool
$c<= :: IRIAuth -> IRIAuth -> Bool
< :: IRIAuth -> IRIAuth -> Bool
$c< :: IRIAuth -> IRIAuth -> Bool
compare :: IRIAuth -> IRIAuth -> Ordering
$ccompare :: IRIAuth -> IRIAuth -> Ordering
$cp1Ord :: Eq IRIAuth
Ord
, ReadPrec [IRIAuth]
ReadPrec IRIAuth
Int -> ReadS IRIAuth
ReadS [IRIAuth]
(Int -> ReadS IRIAuth)
-> ReadS [IRIAuth]
-> ReadPrec IRIAuth
-> ReadPrec [IRIAuth]
-> Read IRIAuth
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [IRIAuth]
$creadListPrec :: ReadPrec [IRIAuth]
readPrec :: ReadPrec IRIAuth
$creadPrec :: ReadPrec IRIAuth
readList :: ReadS [IRIAuth]
$creadList :: ReadS [IRIAuth]
readsPrec :: Int -> ReadS IRIAuth
$creadsPrec :: Int -> ReadS IRIAuth
Read
, Int -> IRIAuth -> ShowS
[IRIAuth] -> ShowS
IRIAuth -> String
(Int -> IRIAuth -> ShowS)
-> (IRIAuth -> String) -> ([IRIAuth] -> ShowS) -> Show IRIAuth
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IRIAuth] -> ShowS
$cshowList :: [IRIAuth] -> ShowS
show :: IRIAuth -> String
$cshow :: IRIAuth -> String
showsPrec :: Int -> IRIAuth -> ShowS
$cshowsPrec :: Int -> IRIAuth -> ShowS
Show
, (forall x. IRIAuth -> Rep IRIAuth x)
-> (forall x. Rep IRIAuth x -> IRIAuth) -> Generic IRIAuth
forall x. Rep IRIAuth x -> IRIAuth
forall x. IRIAuth -> Rep IRIAuth x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep IRIAuth x -> IRIAuth
$cfrom :: forall x. IRIAuth -> Rep IRIAuth x
Generic
, IRIAuth -> ()
(IRIAuth -> ()) -> NFData IRIAuth
forall a. (a -> ()) -> NFData a
rnf :: IRIAuth -> ()
$crnf :: IRIAuth -> ()
NFData
)
isIRI :: Char -> Bool
isIRI :: Char -> Bool
isIRI Char
c = (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'<')
Bool -> Bool -> Bool
&& (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'>')
Bool -> Bool -> Bool
&& (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'"')
Bool -> Bool -> Bool
&& (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'{')
Bool -> Bool -> Bool
&& (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'}')
Bool -> Bool -> Bool
&& (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'|')
Bool -> Bool -> Bool
&& (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'^')
Bool -> Bool -> Bool
&& (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'`')
Bool -> Bool -> Bool
&& (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'\\')
parseIRI :: A.Parser IRI
parseIRI :: Parser IRI
parseIRI = Text -> Maybe IRIAuth -> Text -> Maybe Text -> Maybe Text -> IRI
IRI (Text -> Maybe IRIAuth -> Text -> Maybe Text -> Maybe Text -> IRI)
-> Parser Text Text
-> Parser
Text (Maybe IRIAuth -> Text -> Maybe Text -> Maybe Text -> IRI)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Parser Text Text
parseScheme Parser Text Text -> Parser Text Char -> Parser Text Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> Parser Text Char
A.char Char
':')
Parser
Text (Maybe IRIAuth -> Text -> Maybe Text -> Maybe Text -> IRI)
-> Parser Text (Maybe IRIAuth)
-> Parser Text (Text -> Maybe Text -> Maybe Text -> IRI)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Text (Maybe IRIAuth)
parseAuth
Parser Text (Text -> Maybe Text -> Maybe Text -> IRI)
-> Parser Text Text
-> Parser Text (Maybe Text -> Maybe Text -> IRI)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Text Text
parsePath
Parser Text (Maybe Text -> Maybe Text -> IRI)
-> Parser Text (Maybe Text) -> Parser Text (Maybe Text -> IRI)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Text (Maybe Text)
parseQuery
Parser Text (Maybe Text -> IRI)
-> Parser Text (Maybe Text) -> Parser IRI
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Text (Maybe Text)
parseFragment
parseScheme :: A.Parser T.Text
parseScheme :: Parser Text Text
parseScheme = (Char -> Bool) -> Parser Text Text
A.takeWhile1 Char -> Bool
isScheme Parser Text Text -> (Text -> Parser Text Text) -> Parser Text Text
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Parser Text Text
forall (f :: * -> *). MonadFail f => Text -> f Text
check
where check :: Text -> f Text
check Text
t
| Char -> Bool
isAlpha (Text -> Char
T.head Text
t) = Text -> f Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
t
| Bool
otherwise = String -> f Text
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"parseScheme: must start with letter."
isScheme :: Char -> Bool
isScheme Char
c = Char -> Bool
isAlphaNum Char
c
Bool -> Bool -> Bool
|| (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'+')
Bool -> Bool -> Bool
|| (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-')
Bool -> Bool -> Bool
|| (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.')
parseAuth :: A.Parser (Maybe IRIAuth)
parseAuth :: Parser Text (Maybe IRIAuth)
parseAuth = Maybe IRIAuth
-> Parser Text (Maybe IRIAuth) -> Parser Text (Maybe IRIAuth)
forall (f :: * -> *) a. Alternative f => a -> f a -> f a
A.option Maybe IRIAuth
forall a. Maybe a
Nothing (Text -> Parser Text Text
A.string Text
"//" Parser Text Text
-> Parser Text (Maybe IRIAuth) -> Parser Text (Maybe IRIAuth)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (IRIAuth -> Maybe IRIAuth
forall a. a -> Maybe a
Just (IRIAuth -> Maybe IRIAuth)
-> Parser Text IRIAuth -> Parser Text (Maybe IRIAuth)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Text IRIAuth
parseIRIAuth))
where parseIRIAuth :: Parser Text IRIAuth
parseIRIAuth = Maybe Text -> Text -> Maybe Text -> IRIAuth
IRIAuth (Maybe Text -> Text -> Maybe Text -> IRIAuth)
-> Parser Text (Maybe Text)
-> Parser Text (Text -> Maybe Text -> IRIAuth)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Text (Maybe Text)
parseUser
Parser Text (Text -> Maybe Text -> IRIAuth)
-> Parser Text Text -> Parser Text (Maybe Text -> IRIAuth)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Text Text
parseHost
Parser Text (Maybe Text -> IRIAuth)
-> Parser Text (Maybe Text) -> Parser Text IRIAuth
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Text (Maybe Text)
parsePort
parseUser :: A.Parser (Maybe T.Text)
parseUser :: Parser Text (Maybe Text)
parseUser = Maybe Text -> Parser Text (Maybe Text) -> Parser Text (Maybe Text)
forall (f :: * -> *) a. Alternative f => a -> f a -> f a
A.option Maybe Text
forall a. Maybe a
Nothing (Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text)
-> Parser Text Text -> Parser Text (Maybe Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((Char -> Bool) -> Parser Text Text
A.takeWhile1 Char -> Bool
isUser Parser Text Text -> Parser Text Char -> Parser Text Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> Parser Text Char
A.char Char
'@'))
where isUser :: Char -> Bool
isUser Char
c = Char -> Bool
isIRI Char
c Bool -> Bool -> Bool
&& (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'@')
parseHost :: A.Parser T.Text
parseHost :: Parser Text Text
parseHost = (Char -> Bool) -> Parser Text Text
A.takeWhile1 Char -> Bool
isHost
where isHost :: Char -> Bool
isHost Char
c = Char -> Bool
isIRI Char
c Bool -> Bool -> Bool
&& (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'/') Bool -> Bool -> Bool
&& (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
':')
parsePort :: A.Parser (Maybe T.Text)
parsePort :: Parser Text (Maybe Text)
parsePort = Maybe Text -> Parser Text (Maybe Text) -> Parser Text (Maybe Text)
forall (f :: * -> *) a. Alternative f => a -> f a -> f a
A.option Maybe Text
forall a. Maybe a
Nothing (Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text)
-> Parser Text Text -> Parser Text (Maybe Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Char -> Parser Text Char
A.char Char
':' Parser Text Char -> Parser Text Text -> Parser Text Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (Char -> Bool) -> Parser Text Text
A.takeWhile1 Char -> Bool
isDigit))
parsePath :: A.Parser T.Text
parsePath :: Parser Text Text
parsePath = Text -> Parser Text Text -> Parser Text Text
forall (f :: * -> *) a. Alternative f => a -> f a -> f a
A.option Text
"" (Char -> Parser Text Char
A.char Char
'/' Parser Text Char -> Parser Text Text -> Parser Text Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (Char -> Bool) -> Parser Text Text
A.takeWhile1 Char -> Bool
isPath)
where isPath :: Char -> Bool
isPath Char
c = Char -> Bool
isIRI Char
c Bool -> Bool -> Bool
&& (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'?') Bool -> Bool -> Bool
&& (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'#')
parseQuery :: A.Parser (Maybe T.Text)
parseQuery :: Parser Text (Maybe Text)
parseQuery = Maybe Text -> Parser Text (Maybe Text) -> Parser Text (Maybe Text)
forall (f :: * -> *) a. Alternative f => a -> f a -> f a
A.option Maybe Text
forall a. Maybe a
Nothing (Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text)
-> Parser Text Text -> Parser Text (Maybe Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Char -> Parser Text Char
A.char Char
'?' Parser Text Char -> Parser Text Text -> Parser Text Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (Char -> Bool) -> Parser Text Text
A.takeWhile1 Char -> Bool
isQuery))
where isQuery :: Char -> Bool
isQuery Char
c = Char -> Bool
isIRI Char
c Bool -> Bool -> Bool
&& (Char
cChar -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'#')
parseFragment :: A.Parser (Maybe T.Text)
parseFragment :: Parser Text (Maybe Text)
parseFragment = Maybe Text -> Parser Text (Maybe Text) -> Parser Text (Maybe Text)
forall (f :: * -> *) a. Alternative f => a -> f a -> f a
A.option Maybe Text
forall a. Maybe a
Nothing (Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text)
-> Parser Text Text -> Parser Text (Maybe Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Char -> Parser Text Char
A.char Char
'#' Parser Text Char -> Parser Text Text -> Parser Text Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (Char -> Bool) -> Parser Text Text
A.takeWhile1 Char -> Bool
isIRI))
parseGraphLabel :: A.Parser (Maybe IRI)
parseGraphLabel :: Parser (Maybe IRI)
parseGraphLabel = Maybe IRI -> Parser (Maybe IRI) -> Parser (Maybe IRI)
forall (f :: * -> *) a. Alternative f => a -> f a -> f a
A.option Maybe IRI
forall a. Maybe a
Nothing (IRI -> Maybe IRI
forall a. a -> Maybe a
Just (IRI -> Maybe IRI) -> Parser IRI -> Parser (Maybe IRI)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser IRI
parseEscapedIRI)
parseSubject :: A.Parser Subject
parseSubject :: Parser Subject
parseSubject = do
Char
c <- Parser Text Char
A.anyChar
case Char
c of Char
'<' -> IRI -> Subject
IRISubject (IRI -> Subject) -> Parser IRI -> Parser Subject
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Parser IRI
parseIRI Parser IRI -> Parser Text Char -> Parser IRI
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> Parser Text Char
A.char Char
'>')
Char
'_' -> BlankNode -> Subject
BlankSubject (BlankNode -> Subject) -> Parser Text BlankNode -> Parser Subject
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Char -> Parser Text Char
A.char Char
':' Parser Text Char -> Parser Text BlankNode -> Parser Text BlankNode
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser Text BlankNode
parseBlankNodeLabel)
Char
_ -> String -> Parser Subject
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"parseSubject: must be blank node or IRI."
parsePredicate :: A.Parser Predicate
parsePredicate :: Parser Predicate
parsePredicate = IRI -> Predicate
Predicate (IRI -> Predicate) -> Parser IRI -> Parser Predicate
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser IRI
parseEscapedIRI
parseObject :: A.Parser Object
parseObject :: Parser Object
parseObject = do
Char
c <- Parser Text Char
A.anyChar
case Char
c of Char
'<' -> IRI -> Object
IRIObject (IRI -> Object) -> Parser IRI -> Parser Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Parser IRI
parseIRI Parser IRI -> Parser Text Char -> Parser IRI
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> Parser Text Char
A.char Char
'>')
Char
'_' -> BlankNode -> Object
BlankObject (BlankNode -> Object) -> Parser Text BlankNode -> Parser Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Char -> Parser Text Char
A.char Char
':' Parser Text Char -> Parser Text BlankNode -> Parser Text BlankNode
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser Text BlankNode
parseBlankNodeLabel)
Char
_ -> Literal -> Object
LiteralObject (Literal -> Object) -> Parser Text Literal -> Parser Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Text Literal
parseLiteralBody
parseEscapedIRI :: A.Parser IRI
parseEscapedIRI :: Parser IRI
parseEscapedIRI = Char -> Parser Text Char
A.char Char
'<' Parser Text Char -> Parser IRI -> Parser IRI
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser IRI
parseIRI Parser IRI -> Parser Text Char -> Parser IRI
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> Parser Text Char
A.char Char
'>'
parseBlankNodeLabel :: A.Parser BlankNode
parseBlankNodeLabel :: Parser Text BlankNode
parseBlankNodeLabel = Text -> BlankNode
BlankNode (Text -> BlankNode) -> Parser Text Text -> Parser Text BlankNode
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((Char -> Bool) -> Parser Text Text
A.takeWhile1 Char -> Bool
isLabel Parser Text Text -> (Text -> Parser Text Text) -> Parser Text Text
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Parser Text Text
forall (f :: * -> *). MonadFail f => Text -> f Text
check)
where check :: Text -> f Text
check Text
t
| Char -> Bool
isHead (Text -> Char
T.head Text
t) Bool -> Bool -> Bool
&& Char -> Bool
isTail (Text -> Char
T.last Text
t) = Text -> f Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
t
| Bool
otherwise = String -> f Text
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"parseBlankNode"
isLabel :: Char -> Bool
isLabel = Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
isSpace
isHead :: Char -> Bool
isHead Char
c = Char -> Bool
isLabel Char
c
Bool -> Bool -> Bool
&& (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'-')
Bool -> Bool -> Bool
&& (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'.')
isTail :: Char -> Bool
isTail Char
c = Char -> Bool
isLabel Char
c
Bool -> Bool -> Bool
&& (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'.')
parseBlankNode :: A.Parser BlankNode
parseBlankNode :: Parser Text BlankNode
parseBlankNode = Text -> Parser Text Text
A.string Text
"_:" Parser Text Text -> Parser Text BlankNode -> Parser Text BlankNode
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser Text BlankNode
parseBlankNodeLabel
parseLiteralBody :: A.Parser Literal
parseLiteralBody :: Parser Text Literal
parseLiteralBody = Text -> LiteralType -> Literal
Literal (Text -> LiteralType -> Literal)
-> Parser Text Text -> Parser Text (LiteralType -> Literal)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Text Text
escString Parser Text (LiteralType -> Literal)
-> Parser Text LiteralType -> Parser Text Literal
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Text LiteralType
valType
where valType :: Parser Text LiteralType
valType = Parser Text LiteralType
valIRIType Parser Text LiteralType
-> Parser Text LiteralType -> Parser Text LiteralType
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser Text LiteralType
valLangType Parser Text LiteralType
-> Parser Text LiteralType -> Parser Text LiteralType
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> LiteralType -> Parser Text LiteralType
forall (f :: * -> *) a. Applicative f => a -> f a
pure LiteralType
LiteralUntyped
valIRIType :: Parser Text LiteralType
valIRIType = IRI -> LiteralType
LiteralIRIType (IRI -> LiteralType) -> Parser IRI -> Parser Text LiteralType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Text -> Parser Text Text
A.string Text
"^^" Parser Text Text -> Parser IRI -> Parser IRI
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser IRI
parseEscapedIRI)
valLangType :: Parser Text LiteralType
valLangType = Text -> LiteralType
LiteralLangType (Text -> LiteralType)
-> Parser Text Text -> Parser Text LiteralType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Char -> Parser Text Char
A.char Char
'@' Parser Text Char -> Parser Text Text -> Parser Text Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (Char -> Bool) -> Parser Text Text
A.takeWhile1 Char -> Bool
isLang)
isLang :: Char -> Bool
isLang Char
c = Char -> Bool
isAlphaNum Char
c Bool -> Bool -> Bool
|| (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-')
escString :: Parser Text Text
escString = Text -> Text
unescapeAll (Text -> Text) -> Parser Text Text -> Parser Text Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Bool -> (Bool -> Char -> Maybe Bool) -> Parser Text Text
forall s. s -> (s -> Char -> Maybe s) -> Parser Text Text
A.scan Bool
False Bool -> Char -> Maybe Bool
machine
machine :: Bool -> Char -> Maybe Bool
machine Bool
False Char
'\\' = Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True
machine Bool
False Char
'"' = Maybe Bool
forall a. Maybe a
Nothing
machine Bool
False Char
_ = Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
False
machine Bool
True Char
_ = Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
False
unescapeAll :: Text -> Text
unescapeAll = [Text] -> Text
T.concat ([Text] -> Text) -> (Text -> [Text]) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> [Text]
unescapeFrag ([Text] -> [Text]) -> (Text -> [Text]) -> Text -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> [Text]
T.splitOn Text
"\\"
unescapeFrag :: [Text] -> [Text]
unescapeFrag [] = []
unescapeFrag (Text
f:[Text]
fs) = case Text -> Maybe (Char, Text)
T.uncons Text
f of
Maybe (Char, Text)
Nothing -> Text
f Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: [Text] -> [Text]
unescapeFrag [Text]
fs
(Just (Char
e, Text
f')) -> Char -> Text
T.singleton (Char -> Char
unescape Char
e) Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: Text
f' Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: [Text] -> [Text]
unescapeFrag [Text]
fs
unescape :: Char -> Char
unescape Char
't' = Char
'\t'
unescape Char
'b' = Char
'\b'
unescape Char
'n' = Char
'\n'
unescape Char
'r' = Char
'\r'
unescape Char
'f' = Char
'\f'
unescape Char
c = Char
c
parseLiteral :: A.Parser Literal
parseLiteral :: Parser Text Literal
parseLiteral = Char -> Parser Text Char
A.char Char
'"' Parser Text Char -> Parser Text Literal -> Parser Text Literal
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser Text Literal
parseLiteralBody
parseUnescapedLiteral :: A.Parser Literal
parseUnescapedLiteral :: Parser Text Literal
parseUnescapedLiteral = Text -> LiteralType -> Literal
Literal (Text -> LiteralType -> Literal)
-> Parser Text Text -> Parser Text (LiteralType -> Literal)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Text Text
A.takeText Parser Text (LiteralType -> Literal)
-> Parser Text LiteralType -> Parser Text Literal
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> LiteralType -> Parser Text LiteralType
forall (f :: * -> *) a. Applicative f => a -> f a
pure LiteralType
LiteralUntyped
fromStringParser :: A.Parser a
-> String
-> (String -> a)
fromStringParser :: Parser a -> String -> String -> a
fromStringParser Parser a
p String
n String
s = let t :: Text
t = String -> Text
T.pack String
s
r :: Either String a
r = Parser a -> Text -> Either String a
forall a. Parser a -> Text -> Either String a
A.parseOnly Parser a
p Text
t
in case Either String a
r of (Left String
e) -> String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall a. Monoid a => [a] -> a
mconcat
[ String
"Invalid "
, String
n
, String
" literal ("
, String
s
, String
") "
, String
e
]
(Right a
x) -> a
x
instance IsString IRI where
fromString :: String -> IRI
fromString = Parser IRI -> String -> String -> IRI
forall a. Parser a -> String -> String -> a
fromStringParser Parser IRI
parseIRI String
"IRI"
instance IsString Literal where
fromString :: String -> Literal
fromString = Parser Text Literal -> String -> String -> Literal
forall a. Parser a -> String -> String -> a
fromStringParser Parser Text Literal
p String
"Literal"
where p :: Parser Text Literal
p = Parser Text Literal
parseLiteral Parser Text Literal -> Parser Text Literal -> Parser Text Literal
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser Text Literal
parseUnescapedLiteral
instance IsString BlankNode where
fromString :: String -> BlankNode
fromString = Parser Text BlankNode -> String -> String -> BlankNode
forall a. Parser a -> String -> String -> a
fromStringParser Parser Text BlankNode
parseBlankNode String
"BlankNode"
instance IsString Subject where
fromString :: String -> Subject
fromString = Parser Subject -> String -> String -> Subject
forall a. Parser a -> String -> String -> a
fromStringParser Parser Subject
parseSubject String
"Subject"
instance IsString Predicate where
fromString :: String -> Predicate
fromString = Parser Predicate -> String -> String -> Predicate
forall a. Parser a -> String -> String -> a
fromStringParser Parser Predicate
parsePredicate String
"Predicate"
instance IsString Object where
fromString :: String -> Object
fromString = Parser Object -> String -> String -> Object
forall a. Parser a -> String -> String -> a
fromStringParser Parser Object
p String
"Object"
where p :: Parser Object
p = Parser Object
parseObject Parser Object -> Parser Object -> Parser Object
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Literal -> Object
LiteralObject (Literal -> Object) -> Parser Text Literal -> Parser Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Text Literal
parseUnescapedLiteral)