rdf-0.1.0.1: Representation and Incremental Processing of RDF Data

CopyrightTravis Whitaker 2016
LicenseMIT
Maintainerpi.boy.travis@gmail.com
StabilityProvisional
PortabilityPortable
Safe HaskellSafe
LanguageHaskell2010

Data.RDF.Types

Contents

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.

data Quad Source

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

Constructors

Quad 

Fields

quadTriple :: !Triple
 
quadGraph :: !(Maybe IRI)
 

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

Eq Subject Source 
Ord Subject Source 
Read Subject Source 
Show Subject Source 
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.

Generic Subject Source 
NFData Subject Source 
type Rep Subject Source 

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

unPredicate :: IRI
 

Instances

Eq Predicate Source 
Ord Predicate Source 
Read Predicate Source 
Show Predicate Source 
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.

Generic Predicate Source 
NFData Predicate Source 
type Rep Predicate Source 

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

Eq Object Source 
Ord Object Source 
Read Object Source 
Show Object Source 
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.

Generic Object Source 
NFData Object Source 
type Rep Object Source 

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

unBlankNode :: Text
 

Instances

Eq BlankNode Source 
Ord BlankNode Source 
Read BlankNode Source 
Show BlankNode Source 
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.

Generic BlankNode Source 
NFData BlankNode Source 
type Rep BlankNode Source 

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

Eq Literal Source 
Ord Literal Source 
Read Literal Source 
Show Literal Source 
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.

Generic Literal Source 
NFData Literal Source 
type Rep Literal Source 

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.

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

iriScheme :: !Text

The IRI scheme, e.g. http

iriAuth :: !(Maybe IRIAuth)

The IRI authority, e.g. example.com

iriPath :: !Text

The IRI path, e.g. posts/index.html

iriQuery :: !(Maybe Text)

The IRI query, i.e. the component after the ? if present.

iriFragment :: !(Maybe Text)

The IRI fragment, i.e. the component after the # if present.

Instances

Eq IRI Source 
Ord IRI Source 
Read IRI Source 
Show IRI Source 
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.

Generic IRI Source 
NFData IRI Source 
type Rep IRI Source 

data IRIAuth Source

An IRI Authority, as described by RFC 3987.

Constructors

IRIAuth 

Fields

iriUser :: !(Maybe Text)

The IRI user, i.e. the component before the @ if present.

iriHost :: Text

The IRI host, e.g. example.com.

iriPort :: !(Maybe Text)

The IRI port, i.e. the numeral after the : if present.