rdf4h-4.0.0: A library for RDF processing in Haskell

Safe HaskellNone
LanguageHaskell98

Data.RDF.Types

Contents

Synopsis

RDF triples, nodes and literals

data LValue Source #

The actual value of an RDF literal, represented as the LValue parameter of an LNode.

Constructors

PlainL !Text

A plain (untyped) literal value in an unspecified language.

PlainLL !Text !Text

A plain (untyped) literal value with a language specifier.

TypedL !Text !Text

A typed literal value consisting of the literal value and the URI of the datatype of the value, respectively.

Instances
Eq LValue Source #

Two LValue values are equal iff they are of the same type and all fields are equal.

Instance details

Defined in Data.RDF.Types

Methods

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

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

Ord LValue Source #

Ordering of LValue values is as follows: (PlainL _) < (PlainLL _ _) < (TypedL _ _), and values of the same type are ordered by field values, with '(PlainLL literalValue language)' being ordered by language first and literal value second, and '(TypedL literalValue datatypeUri)' being ordered by datatype first and literal value second.

Instance details

Defined in Data.RDF.Types

Show LValue Source # 
Instance details

Defined in Data.RDF.Types

Generic LValue Source # 
Instance details

Defined in Data.RDF.Types

Associated Types

type Rep LValue :: Type -> Type #

Methods

from :: LValue -> Rep LValue x #

to :: Rep LValue x -> LValue #

Hashable LValue Source # 
Instance details

Defined in Data.RDF.Types

Methods

hashWithSalt :: Int -> LValue -> Int #

hash :: LValue -> Int #

Binary LValue Source # 
Instance details

Defined in Data.RDF.Types

Methods

put :: LValue -> Put #

get :: Get LValue #

putList :: [LValue] -> Put #

NFData LValue Source # 
Instance details

Defined in Data.RDF.Types

Methods

rnf :: LValue -> () #

type Rep LValue Source # 
Instance details

Defined in Data.RDF.Types

data Node Source #

An RDF node, which may be either a URIRef node (UNode), a blank node (BNode), or a literal node (LNode).

Constructors

UNode !Text

An RDF URI reference. URIs conform to the RFC3986 standard. See http://www.w3.org/TR/rdf-concepts/#section-Graph-URIref for more information.

BNode !Text

An RDF blank node. See http://www.w3.org/TR/rdf-concepts/#section-blank-nodes for more information.

BNodeGen !Int

An RDF blank node with an auto-generated identifier, as used in Turtle.

LNode !LValue

An RDF literal. See http://www.w3.org/TR/rdf-concepts/#section-Graph-Literal for more information.

Instances
Eq Node Source #

A node is equal to another node if they are both the same type of node and if the field values are equal.

Instance details

Defined in Data.RDF.Types

Methods

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

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

Ord Node Source #

Node ordering is defined first by type, with Unode < BNode < BNodeGen < LNode PlainL < LNode PlainLL < LNode TypedL, and secondly by the natural ordering of the node value.

E.g., a '(UNode _)' is LT any other type of node, and a '(LNode (TypedL _ _))' is GT any other type of node, and the ordering of '(BNodeGen 44)' and '(BNodeGen 3)' is that of the values, or 'compare 44 3', GT.

Instance details

Defined in Data.RDF.Types

Methods

compare :: Node -> Node -> Ordering #

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

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

(>) :: Node -> Node -> Bool #

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

max :: Node -> Node -> Node #

min :: Node -> Node -> Node #

Show Node Source # 
Instance details

Defined in Data.RDF.Types

Methods

showsPrec :: Int -> Node -> ShowS #

show :: Node -> String #

showList :: [Node] -> ShowS #

Generic Node Source # 
Instance details

Defined in Data.RDF.Types

Associated Types

type Rep Node :: Type -> Type #

Methods

from :: Node -> Rep Node x #

to :: Rep Node x -> Node #

Hashable Node Source # 
Instance details

Defined in Data.RDF.Types

Methods

hashWithSalt :: Int -> Node -> Int #

hash :: Node -> Int #

Binary Node Source # 
Instance details

Defined in Data.RDF.Types

Methods

put :: Node -> Put #

get :: Get Node #

putList :: [Node] -> Put #

NFData Node Source # 
Instance details

Defined in Data.RDF.Types

Methods

rnf :: Node -> () #

type Rep Node Source # 
Instance details

Defined in Data.RDF.Types

type Subject = Node Source #

An alias for Node, defined for convenience and readability purposes.

type Predicate = Node Source #

An alias for Node, defined for convenience and readability purposes.

type Object = Node Source #

An alias for Node, defined for convenience and readability purposes.

data Triple Source #

An RDF triple is a statement consisting of a subject, predicate, and object, respectively.

See http://www.w3.org/TR/rdf-concepts/#section-triples for more information.

Constructors

Triple !Node !Node !Node 
Instances
Eq Triple Source #

Two triples are equal iff their respective subjects, predicates, and objects are equal.

Instance details

Defined in Data.RDF.Types

Methods

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

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

Ord Triple Source #

The ordering of triples is based on that of the subject, predicate, and object of the triple, in that order.

Instance details

Defined in Data.RDF.Types

Show Triple Source # 
Instance details

Defined in Data.RDF.Types

Generic Triple Source # 
Instance details

Defined in Data.RDF.Types

Associated Types

type Rep Triple :: Type -> Type #

Methods

from :: Triple -> Rep Triple x #

to :: Rep Triple x -> Triple #

Binary Triple Source # 
Instance details

Defined in Data.RDF.Types

Methods

put :: Triple -> Put #

get :: Get Triple #

putList :: [Triple] -> Put #

NFData Triple Source # 
Instance details

Defined in Data.RDF.Types

Methods

rnf :: Triple -> () #

type Rep Triple Source # 
Instance details

Defined in Data.RDF.Types

type Triples = [Triple] Source #

A list of triples. This is defined for convenience and readability.

class View a b where Source #

A type class for ADTs that expose views to clients.

Methods

view :: a -> b Source #

Constructor functions

plainL :: Text -> LValue Source #

Return a PlainL LValue for the given string value.

plainLL :: Text -> Text -> LValue Source #

Return a PlainLL LValue for the given string value and language, respectively.

typedL :: Text -> Text -> LValue Source #

Return a TypedL LValue for the given string value and datatype URI, respectively.

unode :: Text -> Node Source #

Return a URIRef node for the given URI.

bnode :: Text -> Node Source #

Return a blank node using the given string identifier.

lnode :: LValue -> Node Source #

Return a literal node using the given LValue.

triple :: Subject -> Predicate -> Object -> Triple Source #

A smart constructor function for Triple that verifies the node arguments are of the correct type and creates the new Triple if so or calls error. subj must be a UNode or BNode, and pred must be a UNode.

unodeValidate :: Text -> Maybe Node Source #

Validate a URI and return it in a Just UNode if it is valid, otherwise Nothing is returned. Performs the following:

  1. unescape unicode RDF literals
  2. checks validity of this unescaped URI using isURI from URI
  3. if the unescaped URI is valid then Node constructed with UNode

uriValidate :: Text -> Maybe Text Source #

Validate a Text URI and return it in a Just Text if it is valid, otherwise Nothing is returned. See unodeValidate.

Node query function

isUNode :: Node -> Bool Source #

Answer if given node is a URI Ref node.

isLNode :: Node -> Bool Source #

Answer if given node is a literal node.

isBNode :: Node -> Bool Source #

Answer if given node is a blank node.

Miscellaneous

resolveQName :: Text -> PrefixMappings -> Maybe Text Source #

Resolve a prefix using the given prefix mappings.

isAbsoluteUri :: Text -> Bool Source #

returns True if URI is absolute.

mkAbsoluteUrl :: Text -> Text -> Text Source #

Deprecated: Use resolveIRI instead, because mkAbsoluteUrl is a partial function

Make an absolute URL by returning as is if already an absolute URL and otherwise appending the URL to the given base URL.

escapeRDFSyntax :: Text -> Either ParseError Text Source #

Deprecated: Use unescapeUnicode instead

Unescapes Uxxxxxxxx and uxxxx character sequences according to the RDF specification.

unescapeUnicode :: Text -> Either ParseError Text Source #

Unescapes Uxxxxxxxx and uxxxx character sequences according to the RDF specification.

fileSchemeToFilePath :: IsString s => Node -> Maybe s Source #

Removes "file://" schema from URIs in UNode nodes

filePathToUri :: IsString s => FilePath -> Maybe s Source #

Converts a file path to a URI with "file:" scheme

RDF data family

data family RDF a Source #

RDF data family

Instances
Rdf a => Show (RDF a) Source # 
Instance details

Defined in Data.RDF.Types

Methods

showsPrec :: Int -> RDF a -> ShowS #

show :: RDF a -> String #

showList :: [RDF a] -> ShowS #

Generic (RDF TList) Source # 
Instance details

Defined in Data.RDF.Graph.TList

Associated Types

type Rep (RDF TList) :: Type -> Type #

Methods

from :: RDF TList -> Rep (RDF TList) x #

to :: Rep (RDF TList) x -> RDF TList #

Generic (RDF AlgebraicGraph) Source # 
Instance details

Defined in Data.RDF.Graph.AlgebraicGraph

Associated Types

type Rep (RDF AlgebraicGraph) :: Type -> Type #

Generic (RDF AdjHashMap) Source # 
Instance details

Defined in Data.RDF.Graph.AdjHashMap

Associated Types

type Rep (RDF AdjHashMap) :: Type -> Type #

NFData (RDF TList) Source # 
Instance details

Defined in Data.RDF.Graph.TList

Methods

rnf :: RDF TList -> () #

NFData (RDF AlgebraicGraph) Source # 
Instance details

Defined in Data.RDF.Graph.AlgebraicGraph

Methods

rnf :: RDF AlgebraicGraph -> () #

NFData (RDF AdjHashMap) Source # 
Instance details

Defined in Data.RDF.Graph.AdjHashMap

Methods

rnf :: RDF AdjHashMap -> () #

data RDF TList Source # 
Instance details

Defined in Data.RDF.Graph.TList

data RDF AlgebraicGraph Source # 
Instance details

Defined in Data.RDF.Graph.AlgebraicGraph

data RDF AdjHashMap Source # 
Instance details

Defined in Data.RDF.Graph.AdjHashMap

type Rep (RDF TList) Source # 
Instance details

Defined in Data.RDF.Graph.TList

type Rep (RDF TList) = D1 (MetaData "RDF" "Data.RDF.Graph.TList" "rdf4h-4.0.0-GVSpZShnarFD2qNKU0xzq9" False) (C1 (MetaCons "TListC" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Triples, Maybe BaseUrl, PrefixMappings))))
type Rep (RDF AlgebraicGraph) Source # 
Instance details

Defined in Data.RDF.Graph.AlgebraicGraph

type Rep (RDF AlgebraicGraph) = D1 (MetaData "RDF" "Data.RDF.Graph.AlgebraicGraph" "rdf4h-4.0.0-GVSpZShnarFD2qNKU0xzq9" False) (C1 (MetaCons "AlgebraicGraph" PrefixI True) (S1 (MetaSel (Just "_graph") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Graph (HashSet Node) Node)) :*: (S1 (MetaSel (Just "_baseUrl") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe BaseUrl)) :*: S1 (MetaSel (Just "_prefixMappings") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PrefixMappings))))
type Rep (RDF AdjHashMap) Source # 
Instance details

Defined in Data.RDF.Graph.AdjHashMap

Rdf type class

class (Generic rdfImpl, NFData rdfImpl) => Rdf rdfImpl where Source #

An RDF value is a set of (unique) RDF triples, together with the operations defined upon them.

For information about the efficiency of the functions, see the documentation for the particular RDF instance.

For more information about the concept of an RDF graph, see the following: http://www.w3.org/TR/rdf-concepts/#section-rdf-graph.

Methods

baseUrl :: RDF rdfImpl -> Maybe BaseUrl Source #

Return the base URL of this RDF, if any.

prefixMappings :: RDF rdfImpl -> PrefixMappings Source #

Return the prefix mappings defined for this RDF, if any.

addPrefixMappings :: RDF rdfImpl -> PrefixMappings -> Bool -> RDF rdfImpl Source #

Return an RDF with the specified prefix mappings merged with the existing mappings. If the Bool arg is True, then a new mapping for an existing prefix will replace the old mapping; otherwise, the new mapping is ignored.

empty :: RDF rdfImpl Source #

Return an empty RDF.

mkRdf :: Triples -> Maybe BaseUrl -> PrefixMappings -> RDF rdfImpl Source #

Return a RDF containing all the given triples. Handling of duplicates in the input depend on the particular RDF implementation.

addTriple :: RDF rdfImpl -> Triple -> RDF rdfImpl Source #

Adds a triple to an RDF graph.

removeTriple :: RDF rdfImpl -> Triple -> RDF rdfImpl Source #

Removes all occurrences of a triple in an RDF graph.

triplesOf :: RDF rdfImpl -> Triples Source #

Return all triples in the RDF, as a list.

Note that this function returns a list of triples in the RDF as they were added, without removing duplicates and without expanding namespaces.

uniqTriplesOf :: RDF rdfImpl -> Triples Source #

Return unique triples in the RDF, as a list.

This function performs namespace expansion and removal of duplicates.

select :: RDF rdfImpl -> NodeSelector -> NodeSelector -> NodeSelector -> Triples Source #

Select the triples in the RDF that match the given selectors.

The three NodeSelector parameters are optional functions that match the respective subject, predicate, and object of a triple. The triples returned are those in the given graph for which the first selector returns true when called on the subject, the second selector returns true when called on the predicate, and the third selector returns true when called on the ojbect. A Nothing parameter is equivalent to a function that always returns true for the appropriate node; but implementations may be able to much more efficiently answer a select that involves a Nothing parameter rather than an (id True) parameter.

The following call illustrates the use of select, and would result in the selection of all and only the triples that have a blank node as subject and a literal node as object:

select gr (Just isBNode) Nothing (Just isLNode)

Note: this function may be very slow; see the documentation for the particular RDF implementation for more information.

query :: RDF rdfImpl -> Maybe Node -> Maybe Node -> Maybe Node -> Triples Source #

Return the triples in the RDF that match the given pattern, where the pattern (3 Maybe Node parameters) is interpreted as a triple pattern.

The Maybe Node params are interpreted as the subject, predicate, and object of a triple, respectively. Just n is true iff the triple has a node equal to n in the appropriate location; Nothing is always true, regardless of the node in the appropriate location.

For example, query rdf (Just n1) Nothing (Just n2) would return all and only the triples that have n1 as subject and n2 as object, regardless of the predicate of the triple.

showGraph :: RDF rdfImpl -> String Source #

pretty prints the RDF graph

Instances
Rdf TList Source # 
Instance details

Defined in Data.RDF.Graph.TList

Rdf AlgebraicGraph Source # 
Instance details

Defined in Data.RDF.Graph.AlgebraicGraph

Rdf AdjHashMap Source # 
Instance details

Defined in Data.RDF.Graph.AdjHashMap

Parsing RDF

class RdfParser p where Source #

An RdfParser is a parser that knows how to parse 1 format of RDF and can parse an RDF document of that type from a string, a file, or a URL. Required configuration options will vary from instance to instance.

Methods

parseString :: Rdf a => p -> Text -> Either ParseFailure (RDF a) Source #

Parse RDF from the given text, yielding a failure with error message or the resultant RDF.

parseFile :: Rdf a => p -> String -> IO (Either ParseFailure (RDF a)) Source #

Parse RDF from the local file with the given path, yielding a failure with error message or the resultant RDF in the IO monad.

parseURL :: Rdf a => p -> String -> IO (Either ParseFailure (RDF a)) Source #

Parse RDF from the remote file with the given HTTP URL (https is not supported), yielding a failure with error message or the resultant graph in the IO monad.

Instances
RdfParser NTriplesParserCustom Source #

NTriplesParser is an instance of RdfParser.

Instance details

Defined in Text.RDF.RDF4H.NTriplesParser

RdfParser NTriplesParser Source #

NTriplesParser is an instance of RdfParser using parsec based parsers.

Instance details

Defined in Text.RDF.RDF4H.NTriplesParser

RdfParser TurtleParserCustom Source #

TurtleParser is an instance of RdfParser using either a parsec or an attoparsec based parser.

Instance details

Defined in Text.RDF.RDF4H.TurtleParser

RdfParser TurtleParser Source #

TurtleParser is an instance of RdfParser using a parsec based parser.

Instance details

Defined in Text.RDF.RDF4H.TurtleParser

RdfParser XmlParser Source # 
Instance details

Defined in Text.RDF.RDF4H.XmlParser

Serializing RDF

class RdfSerializer s where Source #

An RdfSerializer is a serializer of RDF to some particular output format, such as NTriples or Turtle.

Methods

hWriteRdf :: Rdf a => s -> Handle -> RDF a -> IO () Source #

Write the RDF to a file handle using whatever configuration is specified by the first argument.

writeRdf :: Rdf a => s -> RDF a -> IO () Source #

Write the RDF to stdout; equivalent to hWriteRdf stdout.

hWriteH :: Rdf a => s -> Handle -> RDF a -> IO () Source #

Write to the file handle whatever header information is required based on the output format. For example, if serializing to Turtle, this method would write the necessary @prefix declarations and possibly a @baseUrl declaration, whereas for NTriples, there is no header section at all, so this would be a no-op.

writeH :: Rdf a => s -> RDF a -> IO () Source #

Write header information to stdout; equivalent to hWriteRdf stdout.

hWriteTs :: s -> Handle -> Triples -> IO () Source #

Write some triples to a file handle using whatever configuration is specified by the first argument.

WARNING: if the serialization format has header-level information that should be output (e.g., @prefix declarations for Turtle), then you should use hWriteG instead of this method unless you're sure this is safe to use, since otherwise the resultant document will be missing the header information and will not be valid.

writeTs :: s -> Triples -> IO () Source #

Write some triples to stdout; equivalent to hWriteTs stdout.

hWriteT :: s -> Handle -> Triple -> IO () Source #

Write a single triple to the file handle using whatever configuration is specified by the first argument. The same WARNING applies as to hWriteTs.

writeT :: s -> Triple -> IO () Source #

Write a single triple to stdout; equivalent to hWriteT stdout.

hWriteN :: s -> Handle -> Node -> IO () Source #

Write a single node to the file handle using whatever configuration is specified by the first argument. The same WARNING applies as to hWriteTs.

writeN :: s -> Node -> IO () Source #

Write a single node to sdout; equivalent to hWriteN stdout.

Instances
RdfSerializer NTriplesSerializer Source # 
Instance details

Defined in Text.RDF.RDF4H.NTriplesSerializer

RdfSerializer TurtleSerializer Source # 
Instance details

Defined in Text.RDF.RDF4H.TurtleSerializer

Namespaces and Prefixes

data Namespace Source #

Represents a namespace as either a prefix and uri, respectively, or just a uri.

Instances
Eq Namespace Source # 
Instance details

Defined in Data.RDF.Types

Show Namespace Source # 
Instance details

Defined in Data.RDF.Types

newtype PrefixMappings Source #

An alias for a map from prefix to namespace URI.

Constructors

PrefixMappings (Map Text Text) 
Instances
Eq PrefixMappings Source # 
Instance details

Defined in Data.RDF.Types

Ord PrefixMappings Source # 
Instance details

Defined in Data.RDF.Types

Show PrefixMappings Source # 
Instance details

Defined in Data.RDF.Types

Generic PrefixMappings Source # 
Instance details

Defined in Data.RDF.Types

Associated Types

type Rep PrefixMappings :: Type -> Type #

Semigroup PrefixMappings Source # 
Instance details

Defined in Data.RDF.Types

Monoid PrefixMappings Source # 
Instance details

Defined in Data.RDF.Types

Binary PrefixMappings Source # 
Instance details

Defined in Data.RDF.Types

NFData PrefixMappings Source # 
Instance details

Defined in Data.RDF.Types

Methods

rnf :: PrefixMappings -> () #

type Rep PrefixMappings Source # 
Instance details

Defined in Data.RDF.Types

type Rep PrefixMappings = D1 (MetaData "PrefixMappings" "Data.RDF.Types" "rdf4h-4.0.0-GVSpZShnarFD2qNKU0xzq9" True) (C1 (MetaCons "PrefixMappings" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map Text Text))))

Supporting types

newtype BaseUrl Source #

The base URL of an RDF.

Constructors

BaseUrl 

Fields

Instances
Eq BaseUrl Source # 
Instance details

Defined in Data.RDF.Types

Methods

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

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

Ord BaseUrl Source # 
Instance details

Defined in Data.RDF.Types

Show BaseUrl Source # 
Instance details

Defined in Data.RDF.Types

Generic BaseUrl Source # 
Instance details

Defined in Data.RDF.Types

Associated Types

type Rep BaseUrl :: Type -> Type #

Methods

from :: BaseUrl -> Rep BaseUrl x #

to :: Rep BaseUrl x -> BaseUrl #

Semigroup BaseUrl Source # 
Instance details

Defined in Data.RDF.Types

Monoid BaseUrl Source # 
Instance details

Defined in Data.RDF.Types

Binary BaseUrl Source # 
Instance details

Defined in Data.RDF.Types

Methods

put :: BaseUrl -> Put #

get :: Get BaseUrl #

putList :: [BaseUrl] -> Put #

NFData BaseUrl Source # 
Instance details

Defined in Data.RDF.Types

Methods

rnf :: BaseUrl -> () #

type Rep BaseUrl Source # 
Instance details

Defined in Data.RDF.Types

type Rep BaseUrl = D1 (MetaData "BaseUrl" "Data.RDF.Types" "rdf4h-4.0.0-GVSpZShnarFD2qNKU0xzq9" True) (C1 (MetaCons "BaseUrl" PrefixI True) (S1 (MetaSel (Just "unBaseUrl") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

type NodeSelector = Maybe (Node -> Bool) Source #

A NodeSelector is either a function that returns True or False for a node, or Nothing, which indicates that all nodes would return True.

The selector is said to select, or match, the nodes for which it returns True.

When used in conjunction with the select method of Graph, three node selectors are used to match a triple.

newtype ParseFailure Source #

Represents a failure in parsing an N-Triples document, including an error message with information about the cause for the failure.

Constructors

ParseFailure String 
Instances
Eq ParseFailure Source # 
Instance details

Defined in Data.RDF.Types

Show ParseFailure Source # 
Instance details

Defined in Data.RDF.Types