rdf-0.1.0.5: Representation and Incremental Processing of RDF Data
CopyrightTravis Whitaker 2016
LicenseMIT
Maintainerpi.boy.travis@gmail.com
StabilityProvisional
PortabilityPortable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.RDF.Types

Description

This module provides types for representing RDF data based on the abstract syntax described in RDF 1.1 Concepts and Abstract Syntax.

Synopsis

Graphs

data RDFGraph Source #

A contiguous RDF graph with optional label. Note that a contiguous graph within an RDF data set will not appear as a single contiguous graph to this library if the graph's constituent triples are not contiguous in the original data set. This strategy allows for incremental processing of RDF data in constant space.

Constructors

RDFGraph 

Fields

  • rdfLabel :: !(Maybe IRI)

    A named RDF graph includes an IRI.

  • rdfTriples :: [Triple]

    The constituent triples. A proper graph is a strict set of triples (i.e. no duplicate nodes or edges), but this guarantee cannot be made if the triples are to be processed incrementally in constant space. Programs using this type for interpreting RDF graphs should ignore any supernumerary triples in this list.

Instances

Instances details
Eq RDFGraph Source # 
Instance details

Defined in Data.RDF.Internal

Ord RDFGraph Source # 
Instance details

Defined in Data.RDF.Internal

Read RDFGraph Source # 
Instance details

Defined in Data.RDF.Internal

Show RDFGraph Source # 
Instance details

Defined in Data.RDF.Internal

Generic RDFGraph Source # 
Instance details

Defined in Data.RDF.Internal

Associated Types

type Rep RDFGraph :: Type -> Type #

Methods

from :: RDFGraph -> Rep RDFGraph x #

to :: Rep RDFGraph x -> RDFGraph #

NFData RDFGraph Source # 
Instance details

Defined in Data.RDF.Internal

Methods

rnf :: RDFGraph -> () #

type Rep RDFGraph Source # 
Instance details

Defined in Data.RDF.Internal

type Rep RDFGraph = D1 ('MetaData "RDFGraph" "Data.RDF.Internal" "rdf-0.1.0.5-CSMHOHSNBOTIieiIawVYPP" 'False) (C1 ('MetaCons "RDFGraph" 'PrefixI 'True) (S1 ('MetaSel ('Just "rdfLabel") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe IRI)) :*: S1 ('MetaSel ('Just "rdfTriples") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Triple])))

data Quad Source #

An RDF quad, i.e. a triple belonging to a named graph.

Constructors

Quad 

Fields

Instances

Instances details
Eq Quad Source # 
Instance details

Defined in Data.RDF.Internal

Methods

(==) :: Quad -> Quad -> Bool #

(/=) :: Quad -> Quad -> Bool #

Ord Quad Source # 
Instance details

Defined in Data.RDF.Internal

Methods

compare :: Quad -> Quad -> Ordering #

(<) :: Quad -> Quad -> Bool #

(<=) :: Quad -> Quad -> Bool #

(>) :: Quad -> Quad -> Bool #

(>=) :: Quad -> Quad -> Bool #

max :: Quad -> Quad -> Quad #

min :: Quad -> Quad -> Quad #

Read Quad Source # 
Instance details

Defined in Data.RDF.Internal

Show Quad Source # 
Instance details

Defined in Data.RDF.Internal

Methods

showsPrec :: Int -> Quad -> ShowS #

show :: Quad -> String #

showList :: [Quad] -> ShowS #

Generic Quad Source # 
Instance details

Defined in Data.RDF.Internal

Associated Types

type Rep Quad :: Type -> Type #

Methods

from :: Quad -> Rep Quad x #

to :: Rep Quad x -> Quad #

NFData Quad Source # 
Instance details

Defined in Data.RDF.Internal

Methods

rnf :: Quad -> () #

type Rep Quad Source # 
Instance details

Defined in Data.RDF.Internal

type Rep Quad = D1 ('MetaData "Quad" "Data.RDF.Internal" "rdf-0.1.0.5-CSMHOHSNBOTIieiIawVYPP" 'False) (C1 ('MetaCons "Quad" 'PrefixI 'True) (S1 ('MetaSel ('Just "quadTriple") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Triple) :*: S1 ('MetaSel ('Just "quadGraph") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe IRI))))

data Triple Source #

An RDF triple.

Constructors

Triple !Subject !Predicate !Object 

Instances

Instances details
Eq Triple Source # 
Instance details

Defined in Data.RDF.Internal

Methods

(==) :: Triple -> Triple -> Bool #

(/=) :: Triple -> Triple -> Bool #

Ord Triple Source # 
Instance details

Defined in Data.RDF.Internal

Read Triple Source # 
Instance details

Defined in Data.RDF.Internal

Show Triple Source # 
Instance details

Defined in Data.RDF.Internal

Generic Triple Source # 
Instance details

Defined in Data.RDF.Internal

Associated Types

type Rep Triple :: Type -> Type #

Methods

from :: Triple -> Rep Triple x #

to :: Rep Triple x -> Triple #

NFData Triple Source # 
Instance details

Defined in Data.RDF.Internal

Methods

rnf :: Triple -> () #

type Rep Triple Source # 
Instance details

Defined in Data.RDF.Internal

Triple Components

data Subject Source #

An RDF subject, i.e. either an IRI or a BlankNode.

This type has an IsString instance, allowing string literals to be interpreted as Subjects with -XOverloadedStrings, like so:

>>> "<http://example.com> :: Subject
IRISubject (IRI (...))
>>> "_:some-node" :: Subject
BlankSubject (BlankNode {unBlankNode = "some-node"})

Instances

Instances details
Eq Subject Source # 
Instance details

Defined in Data.RDF.Internal

Methods

(==) :: Subject -> Subject -> Bool #

(/=) :: Subject -> Subject -> Bool #

Ord Subject Source # 
Instance details

Defined in Data.RDF.Internal

Read Subject Source # 
Instance details

Defined in Data.RDF.Internal

Show Subject Source # 
Instance details

Defined in Data.RDF.Internal

IsString Subject Source #

This instance uses parseSubject and calls error if the literal is invalid. It is not clear exactly when fromString is evaluated so this error is difficult to explictly catch. This can be solved by ensuring that your Subject literals are eagerly evaluated so any malformed literals can be caught immediately. It would be nicer if this happened at compile time.

Instance details

Defined in Data.RDF.Internal

Methods

fromString :: String -> Subject #

Generic Subject Source # 
Instance details

Defined in Data.RDF.Internal

Associated Types

type Rep Subject :: Type -> Type #

Methods

from :: Subject -> Rep Subject x #

to :: Rep Subject x -> Subject #

NFData Subject Source # 
Instance details

Defined in Data.RDF.Internal

Methods

rnf :: Subject -> () #

type Rep Subject Source # 
Instance details

Defined in Data.RDF.Internal

type Rep Subject = D1 ('MetaData "Subject" "Data.RDF.Internal" "rdf-0.1.0.5-CSMHOHSNBOTIieiIawVYPP" 'False) (C1 ('MetaCons "IRISubject" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 IRI)) :+: C1 ('MetaCons "BlankSubject" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BlankNode)))

newtype Predicate Source #

An RDF predicate.

This type has an IsString instance, allowing string literals to be interpreted as Predicates with -XOverloadedStrings, like so:

>>> "<http://example.com>" :: Predicate
Predicate {unPredicate = IRI (...)}

Constructors

Predicate 

Fields

Instances

Instances details
Eq Predicate Source # 
Instance details

Defined in Data.RDF.Internal

Ord Predicate Source # 
Instance details

Defined in Data.RDF.Internal

Read Predicate Source # 
Instance details

Defined in Data.RDF.Internal

Show Predicate Source # 
Instance details

Defined in Data.RDF.Internal

IsString Predicate Source #

This instance uses parsePredicate and calls error if the literal is invalid. It is not clear exactly when fromString is evaluated so this error is difficult to explictly catch. This can be solved by ensuring that your Predicate literals are eagerly evaluated so any malformed literals can be caught immediately. It would be nicer if this happened at compile time.

Instance details

Defined in Data.RDF.Internal

Generic Predicate Source # 
Instance details

Defined in Data.RDF.Internal

Associated Types

type Rep Predicate :: Type -> Type #

NFData Predicate Source # 
Instance details

Defined in Data.RDF.Internal

Methods

rnf :: Predicate -> () #

type Rep Predicate Source # 
Instance details

Defined in Data.RDF.Internal

type Rep Predicate = D1 ('MetaData "Predicate" "Data.RDF.Internal" "rdf-0.1.0.5-CSMHOHSNBOTIieiIawVYPP" 'True) (C1 ('MetaCons "Predicate" 'PrefixI 'True) (S1 ('MetaSel ('Just "unPredicate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IRI)))

data Object Source #

An RDF object, i.e. either an IRI, a Literal, or a BlankNode.

This type has an IsString instance, allowing string literals to be interpreted as Objects with -XOverloadedStrings, like so:

>>> "<http://example.com>" :: Object
IRIObject (IRI (...))
>>> "_:some-node" :: Object
BlankObject (BlankNode {unBlankNode = "some-node"})
>>> "computer" :: Object
LiteralObject (Literal {litString = "computer", litType = LiteralUntyped})

The precedence for literal interpretation is IRI > BlankNode > Literal. To force a literal that is also a valid blank node label or IRI to be interpreted as a LiteralObject, wrap it in an extra set of double quotes:

>>> "\"_:some-node\"" :: Object
LiteralObject (Literal {litString = "_:some-node", litType = LiteralUntyped})

Instances

Instances details
Eq Object Source # 
Instance details

Defined in Data.RDF.Internal

Methods

(==) :: Object -> Object -> Bool #

(/=) :: Object -> Object -> Bool #

Ord Object Source # 
Instance details

Defined in Data.RDF.Internal

Read Object Source # 
Instance details

Defined in Data.RDF.Internal

Show Object Source # 
Instance details

Defined in Data.RDF.Internal

IsString Object Source #

This instance uses parseObject and calls error if the literal is invalid. It is not clear exactly when fromString is evaluated so this error is difficult to explictly catch. This can be solved by ensuring that your Object literals are eagerly evaluated so any malformed literals can be caught immediately. It would be nicer if this happened at compile time.

Instance details

Defined in Data.RDF.Internal

Methods

fromString :: String -> Object #

Generic Object Source # 
Instance details

Defined in Data.RDF.Internal

Associated Types

type Rep Object :: Type -> Type #

Methods

from :: Object -> Rep Object x #

to :: Rep Object x -> Object #

NFData Object Source # 
Instance details

Defined in Data.RDF.Internal

Methods

rnf :: Object -> () #

type Rep Object Source # 
Instance details

Defined in Data.RDF.Internal

type Rep Object = D1 ('MetaData "Object" "Data.RDF.Internal" "rdf-0.1.0.5-CSMHOHSNBOTIieiIawVYPP" 'False) (C1 ('MetaCons "IRIObject" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 IRI)) :+: (C1 ('MetaCons "BlankObject" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BlankNode)) :+: C1 ('MetaCons "LiteralObject" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Literal))))

Terms

newtype BlankNode Source #

A blank node with its local label, without the preceeding "_:". Other programs processing RDF are permitted to discard these node labels, i.e. all blank node labels are local to a specific representation of an RDF data set.

This type has an IsString instance, allowing string literals to be interpreted as BlankNodes with -XOverloadedStrings, like so:

>>> "_:some-node" :: BlankNode
BlankNode {unBlankNode = "some-node"}

Constructors

BlankNode 

Fields

Instances

Instances details
Eq BlankNode Source # 
Instance details

Defined in Data.RDF.Internal

Ord BlankNode Source # 
Instance details

Defined in Data.RDF.Internal

Read BlankNode Source # 
Instance details

Defined in Data.RDF.Internal

Show BlankNode Source # 
Instance details

Defined in Data.RDF.Internal

IsString BlankNode Source #

This instance uses parseBlankNode and calls error if the literal is invalid. It is not clear exactly when fromString is evaluated so this error is difficult to explictly catch. This can be solved by ensuring that your BlankNode literals are eagerly evaluated so any malformed literals can be caught immediately. It would be nicer if this happened at compile time.

Instance details

Defined in Data.RDF.Internal

Generic BlankNode Source # 
Instance details

Defined in Data.RDF.Internal

Associated Types

type Rep BlankNode :: Type -> Type #

NFData BlankNode Source # 
Instance details

Defined in Data.RDF.Internal

Methods

rnf :: BlankNode -> () #

type Rep BlankNode Source # 
Instance details

Defined in Data.RDF.Internal

type Rep BlankNode = D1 ('MetaData "BlankNode" "Data.RDF.Internal" "rdf-0.1.0.5-CSMHOHSNBOTIieiIawVYPP" 'True) (C1 ('MetaCons "BlankNode" 'PrefixI 'True) (S1 ('MetaSel ('Just "unBlankNode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data Literal Source #

An RDF literal. As stipulated by the RDF standard, the litType is merely metadata; all RDF processing programs must try to handle literals that are ill-typed.

This type has an IsString instance, allowing string literals to be interpreted as Literals with -XOverloadedStrings, like so:

>>> "computer" :: Literal
Literal {litString = "computer", litType = LiteralUntyped}

For untyped literals the extra double quotes are not required. They are required for typed literals:

>>> "\"computer\"@en" :: Literal
Literal {litString = "computer", litType = LiteralLangType "en"}
>>> "\"computer\"^^<http://computer.machine/machine>" :: Literal
Literal { litString = "computer", litType = LiteralIRIType (...)}

Constructors

Literal 

Instances

Instances details
Eq Literal Source # 
Instance details

Defined in Data.RDF.Internal

Methods

(==) :: Literal -> Literal -> Bool #

(/=) :: Literal -> Literal -> Bool #

Ord Literal Source # 
Instance details

Defined in Data.RDF.Internal

Read Literal Source # 
Instance details

Defined in Data.RDF.Internal

Show Literal Source # 
Instance details

Defined in Data.RDF.Internal

IsString Literal Source #

This instance uses parseLiteral and calls error if the literal is invalid. It is not clear exactly when fromString is evaluated so this error is difficult to explictly catch. This can be solved by ensuring that your Literal literals are eagerly evaluated so any malformed literals can be caught immediately. It would be nicer if this happened at compile time.

Instance details

Defined in Data.RDF.Internal

Methods

fromString :: String -> Literal #

Generic Literal Source # 
Instance details

Defined in Data.RDF.Internal

Associated Types

type Rep Literal :: Type -> Type #

Methods

from :: Literal -> Rep Literal x #

to :: Rep Literal x -> Literal #

NFData Literal Source # 
Instance details

Defined in Data.RDF.Internal

Methods

rnf :: Literal -> () #

type Rep Literal Source # 
Instance details

Defined in Data.RDF.Internal

type Rep Literal = D1 ('MetaData "Literal" "Data.RDF.Internal" "rdf-0.1.0.5-CSMHOHSNBOTIieiIawVYPP" 'False) (C1 ('MetaCons "Literal" 'PrefixI 'True) (S1 ('MetaSel ('Just "litString") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "litType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 LiteralType)))

data LiteralType Source #

An RDF literal type. As stipulated by the RDF standard, this is merely metadata; all RDF processing programs must try to handle literals that are ill-typed.

Instances

Instances details
Eq LiteralType Source # 
Instance details

Defined in Data.RDF.Internal

Ord LiteralType Source # 
Instance details

Defined in Data.RDF.Internal

Read LiteralType Source # 
Instance details

Defined in Data.RDF.Internal

Show LiteralType Source # 
Instance details

Defined in Data.RDF.Internal

Generic LiteralType Source # 
Instance details

Defined in Data.RDF.Internal

Associated Types

type Rep LiteralType :: Type -> Type #

NFData LiteralType Source # 
Instance details

Defined in Data.RDF.Internal

Methods

rnf :: LiteralType -> () #

type Rep LiteralType Source # 
Instance details

Defined in Data.RDF.Internal

type Rep LiteralType = D1 ('MetaData "LiteralType" "Data.RDF.Internal" "rdf-0.1.0.5-CSMHOHSNBOTIieiIawVYPP" 'False) (C1 ('MetaCons "LiteralIRIType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 IRI)) :+: (C1 ('MetaCons "LiteralLangType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :+: C1 ('MetaCons "LiteralUntyped" 'PrefixI 'False) (U1 :: Type -> Type)))

IRIs

data IRI Source #

An Internationalized Resource Identifier. This library preferentially follows RFC 3987 over the RDF 1.1 specification, as the two standards disagree about precisely what constitutes an IRI. A notable exception is the handling of IRI fragments; this library follows the RDF 1.1 specification, allowing IRI fragments to occur in absolute IRIs, even though this is expressly prohibited by RFC 3987.

Unlike the network-uri package's behavior with URI fields, this library does not include the sentinel tokens in the parsed fields. For example, when parsing http://example.com, network-uri will provide the string http: as the scheme, while this library will provide http as the scheme.

This type has an IsString instnace, allowing string literals to be interpreted as IRIs with -XOverloadedStrings, like so:

>>> "http://example.com" :: IRI
IRI { iriScheme = "http"
    , iriAuth = Just (IRIAuth { iriUser = Nothing
                              , iriHost = "example.com"
                              , iriPort = Nothing
                              })
    , iriPath = ""
    , iriQuery = Nothing
    , iriFragment = Nothing
    }

Constructors

IRI 

Fields

Instances

Instances details
Eq IRI Source # 
Instance details

Defined in Data.RDF.Internal

Methods

(==) :: IRI -> IRI -> Bool #

(/=) :: IRI -> IRI -> Bool #

Ord IRI Source # 
Instance details

Defined in Data.RDF.Internal

Methods

compare :: IRI -> IRI -> Ordering #

(<) :: IRI -> IRI -> Bool #

(<=) :: IRI -> IRI -> Bool #

(>) :: IRI -> IRI -> Bool #

(>=) :: IRI -> IRI -> Bool #

max :: IRI -> IRI -> IRI #

min :: IRI -> IRI -> IRI #

Read IRI Source # 
Instance details

Defined in Data.RDF.Internal

Show IRI Source # 
Instance details

Defined in Data.RDF.Internal

Methods

showsPrec :: Int -> IRI -> ShowS #

show :: IRI -> String #

showList :: [IRI] -> ShowS #

IsString IRI Source #

This instance uses parseIRI and calls error if the literal is invalid. It is not clear exactly when fromString is evaluated so this error is difficult to explictly catch. This can be solved by ensuring that your IRI literals are eagerly evaluated so any malformed literals can be caught immediately. It would be nicer if this happened at compile time.

Instance details

Defined in Data.RDF.Internal

Methods

fromString :: String -> IRI #

Generic IRI Source # 
Instance details

Defined in Data.RDF.Internal

Associated Types

type Rep IRI :: Type -> Type #

Methods

from :: IRI -> Rep IRI x #

to :: Rep IRI x -> IRI #

NFData IRI Source # 
Instance details

Defined in Data.RDF.Internal

Methods

rnf :: IRI -> () #

type Rep IRI Source # 
Instance details

Defined in Data.RDF.Internal

type Rep IRI = D1 ('MetaData "IRI" "Data.RDF.Internal" "rdf-0.1.0.5-CSMHOHSNBOTIieiIawVYPP" 'False) (C1 ('MetaCons "IRI" 'PrefixI 'True) ((S1 ('MetaSel ('Just "iriScheme") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "iriAuth") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe IRIAuth))) :*: (S1 ('MetaSel ('Just "iriPath") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "iriQuery") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "iriFragment") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text))))))

data IRIAuth Source #

An IRI Authority, as described by RFC 3987.

Constructors

IRIAuth 

Fields

Instances

Instances details
Eq IRIAuth Source # 
Instance details

Defined in Data.RDF.Internal

Methods

(==) :: IRIAuth -> IRIAuth -> Bool #

(/=) :: IRIAuth -> IRIAuth -> Bool #

Ord IRIAuth Source # 
Instance details

Defined in Data.RDF.Internal

Read IRIAuth Source # 
Instance details

Defined in Data.RDF.Internal

Show IRIAuth Source # 
Instance details

Defined in Data.RDF.Internal

Generic IRIAuth Source # 
Instance details

Defined in Data.RDF.Internal

Associated Types

type Rep IRIAuth :: Type -> Type #

Methods

from :: IRIAuth -> Rep IRIAuth x #

to :: Rep IRIAuth x -> IRIAuth #

NFData IRIAuth Source # 
Instance details

Defined in Data.RDF.Internal

Methods

rnf :: IRIAuth -> () #

type Rep IRIAuth Source # 
Instance details

Defined in Data.RDF.Internal

type Rep IRIAuth = D1 ('MetaData "IRIAuth" "Data.RDF.Internal" "rdf-0.1.0.5-CSMHOHSNBOTIieiIawVYPP" 'False) (C1 ('MetaCons "IRIAuth" 'PrefixI 'True) (S1 ('MetaSel ('Just "iriUser") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "iriHost") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "iriPort") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)))))