Maintainer | defanor <defanor@uberspace.net> |
---|---|
Stability | unstable |
Portability | non-portable (GHC extensions are used) |
Safe Haskell | Safe |
Language | Haskell2010 |
Redland RDF library bindings. See the original API for in-depth descriptions.
Library organization
- Raw bindings are provided by Redland.LowLevel. Normally they should not be used directly.
- Refined versions (using Haskell types) of those are provided by
Redland.MidLevel. One should still be careful with the allocated
resources while using those, for instance by using
withNew
. A rule of thumb is that whenever you see anInitializer
, it's a good idea to wrap it intowithNew
. - Utility functions and types are provided by Redland.Util. Those don't strictly correspond to functions of the original API.
Usage example
import Redland input :: String input = "<?xml version=\"1.0\"?>\ \<rdf:RDF xmlns:rdf=\"http://www.w3.org/1999/02/22-rdf-syntax-ns#\"\ \ xmlns:dc=\"http://purl.org/dc/elements/1.1/\">\ \ <rdf:Description rdf:about=\"http://www.dajobe.org/\">\ \ <dc:title>Dave Beckett's Home Page</dc:title>\ \ <dc:creator>Dave Beckett</dc:creator>\ \ <dc:description>The generic home page of Dave Beckett.</dc:description>\ \ </rdf:Description>\ \</rdf:RDF>\ \" main :: IO () main = withWSMU "memory" [] "example" "" "http://example.librdf.org/" $ \world storage model uri -> do -- parse and insert guessingParseStringIntoModel world model uri input -- query withQuery world model "sparql" "SELECT ?foo ?bar ?baz WHERE { ?foo ?bar ?baz }" (Just uri) $ mapM_ print -- search statements withStatements world model (Triple Nothing Nothing Nothing) $ mapM_ print
It prints the following:
[("foo",ResourceNode "http://www.dajobe.org/"),("bar",ResourceNode "http://purl.org/dc/elements/1.1/title"),("baz",LiteralNode "Dave Beckett's Home Page" Nothing)] [("foo",ResourceNode "http://www.dajobe.org/"),("bar",ResourceNode "http://purl.org/dc/elements/1.1/creator"),("baz",LiteralNode "Dave Beckett" Nothing)] [("foo",ResourceNode "http://www.dajobe.org/"),("bar",ResourceNode "http://purl.org/dc/elements/1.1/description"),("baz",LiteralNode "The generic home page of Dave Beckett." Nothing)] Triple {subject = Just (ResourceNode "http://www.dajobe.org/"), predicate = Just (ResourceNode "http://purl.org/dc/elements/1.1/title"), object = Just (LiteralNode "Dave Beckett's Home Page" Nothing)} Triple {subject = Just (ResourceNode "http://www.dajobe.org/"), predicate = Just (ResourceNode "http://purl.org/dc/elements/1.1/creator"), object = Just (LiteralNode "Dave Beckett" Nothing)} Triple {subject = Just (ResourceNode "http://www.dajobe.org/"), predicate = Just (ResourceNode "http://purl.org/dc/elements/1.1/description"), object = Just (LiteralNode "The generic home page of Dave Beckett." Nothing)}
- module Redland.MidLevel
- module Redland.Util
- data RedlandWorld
- data RedlandHash
- data RedlandModel
- data RedlandNode
- data RedlandParser
- data RedlandQuery
- data RedlandQueryResults
- data RedlandStatement
- data RedlandStorage
- data RedlandStream
- data RedlandURI
- data ForeignPtr a :: * -> *
Documentation
module Redland.MidLevel
module Redland.Util
data RedlandWorld Source #
data RedlandHash Source #
data RedlandModel Source #
data RedlandNode Source #
data RedlandParser Source #
data RedlandQuery Source #
data RedlandQueryResults Source #
data RedlandStatement Source #
data RedlandStorage Source #
data RedlandStream Source #
data RedlandURI Source #
data ForeignPtr a :: * -> * #
The type ForeignPtr
represents references to objects that are
maintained in a foreign language, i.e., that are not part of the
data structures usually managed by the Haskell storage manager.
The essential difference between ForeignPtr
s and vanilla memory
references of type Ptr a
is that the former may be associated
with finalizers. A finalizer is a routine that is invoked when
the Haskell storage manager detects that - within the Haskell heap
and stack - there are no more references left that are pointing to
the ForeignPtr
. Typically, the finalizer will, then, invoke
routines in the foreign language that free the resources bound by
the foreign object.
The ForeignPtr
is parameterised in the same way as Ptr
. The
type argument of ForeignPtr
should normally be an instance of
class Storable
.
Eq (ForeignPtr a) | |
Ord (ForeignPtr a) | |
Show (ForeignPtr a) | |