Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data.RDF.Types
Synopsis
- data LValue
- data Node
- type Subject = Node
- type Predicate = Node
- type Object = Node
- data Triple = Triple !Node !Node !Node
- type Triples = [Triple]
- class View a b where
- view :: a -> b
- plainL :: Text -> LValue
- plainLL :: Text -> Text -> LValue
- typedL :: Text -> Text -> LValue
- unode :: Text -> Node
- bnode :: Text -> Maybe Node
- bnodeUnsafe :: Text -> Node
- lnode :: LValue -> Node
- triple :: Subject -> Predicate -> Object -> Triple
- unodeValidate :: Text -> Maybe Node
- uriValidate :: Text -> Maybe Text
- uriValidateString :: String -> Maybe String
- isUNode :: Node -> Bool
- isLNode :: Node -> Bool
- isBNode :: Node -> Bool
- resolveQName :: Text -> PrefixMappings -> Maybe Text
- isAbsoluteUri :: Text -> Bool
- mkAbsoluteUrl :: Text -> Text -> Text
- escapeRDFSyntax :: Text -> Either ParseError Text
- unescapeUnicode :: Text -> Either ParseError Text
- fileSchemeToFilePath :: IsString s => Node -> Maybe s
- filePathToUri :: IsString s => FilePath -> Maybe s
- iriFragment :: (CharParsing m, Monad m) => m Text
- uchar :: (CharParsing m, Monad m) => m Char
- data family RDF a
- class (Generic rdfImpl, NFData rdfImpl) => Rdf rdfImpl where
- baseUrl :: RDF rdfImpl -> Maybe BaseUrl
- prefixMappings :: RDF rdfImpl -> PrefixMappings
- addPrefixMappings :: RDF rdfImpl -> PrefixMappings -> Bool -> RDF rdfImpl
- empty :: RDF rdfImpl
- mkRdf :: Triples -> Maybe BaseUrl -> PrefixMappings -> RDF rdfImpl
- addTriple :: RDF rdfImpl -> Triple -> RDF rdfImpl
- removeTriple :: RDF rdfImpl -> Triple -> RDF rdfImpl
- triplesOf :: RDF rdfImpl -> Triples
- uniqTriplesOf :: RDF rdfImpl -> Triples
- select :: RDF rdfImpl -> NodeSelector -> NodeSelector -> NodeSelector -> Triples
- query :: RDF rdfImpl -> Maybe Node -> Maybe Node -> Maybe Node -> Triples
- showGraph :: RDF rdfImpl -> String
- class RdfParser p where
- parseString :: Rdf a => p -> Text -> Either ParseFailure (RDF a)
- parseFile :: Rdf a => p -> String -> IO (Either ParseFailure (RDF a))
- parseURL :: Rdf a => p -> String -> IO (Either ParseFailure (RDF a))
- class RdfSerializer s where
- hWriteRdf :: Rdf a => s -> Handle -> RDF a -> IO ()
- writeRdf :: Rdf a => s -> RDF a -> IO ()
- hWriteH :: Rdf a => s -> Handle -> RDF a -> IO ()
- writeH :: Rdf a => s -> RDF a -> IO ()
- hWriteTs :: s -> Handle -> Triples -> IO ()
- writeTs :: s -> Triples -> IO ()
- hWriteT :: s -> Handle -> Triple -> IO ()
- writeT :: s -> Triple -> IO ()
- hWriteN :: s -> Handle -> Node -> IO ()
- writeN :: s -> Node -> IO ()
- data Namespace
- newtype PrefixMappings = PrefixMappings (Map Text Text)
- newtype PrefixMapping = PrefixMapping (Text, Text)
- newtype BaseUrl = BaseUrl {}
- type NodeSelector = Maybe (Node -> Bool)
- newtype ParseFailure = ParseFailure String
RDF triples, nodes and literals
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
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
Generic Node Source # | |||||
Defined in Data.RDF.Types Associated Types
| |||||
Show Node Source # | |||||
Binary Node Source # | |||||
NFData Node Source # | |||||
Defined in Data.RDF.Types | |||||
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. | ||||
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. | ||||
Hashable Node Source # | |||||
Defined in Data.RDF.Types | |||||
type Rep Node Source # | |||||
Defined in Data.RDF.Types type Rep Node = D1 ('MetaData "Node" "Data.RDF.Types" "rdf4h-5.2.1-8SEEjUtuki7GxpUpVNakHf" 'False) ((C1 ('MetaCons "UNode" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :+: C1 ('MetaCons "BNode" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))) :+: (C1 ('MetaCons "BNodeGen" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "LNode" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 LValue)))) |
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.
Instances
Generic Triple Source # | |||||
Defined in Data.RDF.Types Associated Types
| |||||
Show Triple Source # | |||||
Binary Triple Source # | |||||
NFData Triple Source # | |||||
Defined in Data.RDF.Types | |||||
Eq Triple Source # | Two triples are equal iff their respective subjects, predicates, and objects are equal. | ||||
Ord Triple Source # | The ordering of triples is based on that of the subject, predicate, and object of the triple, in that order. | ||||
type Rep Triple Source # | |||||
Defined in Data.RDF.Types type Rep Triple = D1 ('MetaData "Triple" "Data.RDF.Types" "rdf4h-5.2.1-8SEEjUtuki7GxpUpVNakHf" 'False) (C1 ('MetaCons "Triple" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Node) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Node) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Node)))) |
A type class for ADTs that expose views to clients.
Constructor functions
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.
bnode :: Text -> Maybe Node Source #
Creates a blank node BNode
with a given label. Checks that
label is a syntactically valid label for a blank node i.e. a
BLANK_NODE_LABEL in
https://www.w3.org/TR/n-triples/#n-triples-grammar . Returns
Nothing
for invalid blank node labels. Blank node labels are
written as "_:abc" for a blank node with label "abc" see
https://www.w3.org/TR/sparql11-query/#QSynBlankNodes .
>>>
bnode "_:abc"
Just (BNode "abc")
>>>
bnode "abc"
Nothing
This does not check that the blank node label is unique for a graph, since the function is not associated with a graph.
bnodeUnsafe :: Text -> Node Source #
Return a blank node using the given label. Does not check that label is a syntactically valid label for a blank node i.e. a BLANK_NODE_LABEL in https://www.w3.org/TR/n-triples/#n-triples-grammar .
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
.
uriValidateString :: String -> Maybe String Source #
Same as uriValidate
, but on String
rather than Text
Node query function
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
iriFragment :: (CharParsing m, Monad m) => m Text Source #
RDF data family
RDF data family
Instances
Generic (RDF AdjHashMap) Source # | |||||
Defined in Data.RDF.Graph.AdjHashMap Associated Types
Methods from :: RDF AdjHashMap -> Rep (RDF AdjHashMap) x # to :: Rep (RDF AdjHashMap) x -> RDF AdjHashMap # | |||||
Generic (RDF AlgebraicGraph) Source # | |||||
Defined in Data.RDF.Graph.AlgebraicGraph Associated Types
Methods from :: RDF AlgebraicGraph -> Rep (RDF AlgebraicGraph) x # to :: Rep (RDF AlgebraicGraph) x -> RDF AlgebraicGraph # | |||||
Generic (RDF TList) Source # | |||||
Defined in Data.RDF.Graph.TList Associated Types
| |||||
Rdf a => Show (RDF a) Source # | |||||
NFData (RDF AdjHashMap) Source # | |||||
Defined in Data.RDF.Graph.AdjHashMap Methods rnf :: RDF AdjHashMap -> () # | |||||
NFData (RDF AlgebraicGraph) Source # | |||||
Defined in Data.RDF.Graph.AlgebraicGraph Methods rnf :: RDF AlgebraicGraph -> () # | |||||
NFData (RDF TList) Source # | |||||
Defined in Data.RDF.Graph.TList | |||||
Monad m => MonadState (RDF rdfImpl) (RdfST rdfImpl m) Source # | |||||
newtype RDF AdjHashMap Source # | |||||
Defined in Data.RDF.Graph.AdjHashMap | |||||
data RDF AlgebraicGraph Source # | |||||
Defined in Data.RDF.Graph.AlgebraicGraph | |||||
newtype RDF TList Source # | |||||
Defined in Data.RDF.Graph.TList | |||||
type Rep (RDF AdjHashMap) Source # | |||||
Defined in Data.RDF.Graph.AdjHashMap | |||||
type Rep (RDF AlgebraicGraph) Source # | |||||
Defined in Data.RDF.Graph.AlgebraicGraph type Rep (RDF AlgebraicGraph) = D1 ('MetaData "RDF" "Data.RDF.Graph.AlgebraicGraph" "rdf4h-5.2.1-8SEEjUtuki7GxpUpVNakHf" '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 TList) Source # | |||||
Defined in Data.RDF.Graph.TList |
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.
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 AdjHashMap Source # | |
Defined in Data.RDF.Graph.AdjHashMap Methods baseUrl :: RDF AdjHashMap -> Maybe BaseUrl Source # prefixMappings :: RDF AdjHashMap -> PrefixMappings Source # addPrefixMappings :: RDF AdjHashMap -> PrefixMappings -> Bool -> RDF AdjHashMap Source # empty :: RDF AdjHashMap Source # mkRdf :: Triples -> Maybe BaseUrl -> PrefixMappings -> RDF AdjHashMap Source # addTriple :: RDF AdjHashMap -> Triple -> RDF AdjHashMap Source # removeTriple :: RDF AdjHashMap -> Triple -> RDF AdjHashMap Source # triplesOf :: RDF AdjHashMap -> Triples Source # uniqTriplesOf :: RDF AdjHashMap -> Triples Source # select :: RDF AdjHashMap -> NodeSelector -> NodeSelector -> NodeSelector -> Triples Source # query :: RDF AdjHashMap -> Maybe Node -> Maybe Node -> Maybe Node -> Triples Source # | |
Rdf AlgebraicGraph Source # | |
Defined in Data.RDF.Graph.AlgebraicGraph Methods baseUrl :: RDF AlgebraicGraph -> Maybe BaseUrl Source # prefixMappings :: RDF AlgebraicGraph -> PrefixMappings Source # addPrefixMappings :: RDF AlgebraicGraph -> PrefixMappings -> Bool -> RDF AlgebraicGraph Source # empty :: RDF AlgebraicGraph Source # mkRdf :: Triples -> Maybe BaseUrl -> PrefixMappings -> RDF AlgebraicGraph Source # addTriple :: RDF AlgebraicGraph -> Triple -> RDF AlgebraicGraph Source # removeTriple :: RDF AlgebraicGraph -> Triple -> RDF AlgebraicGraph Source # triplesOf :: RDF AlgebraicGraph -> Triples Source # uniqTriplesOf :: RDF AlgebraicGraph -> Triples Source # select :: RDF AlgebraicGraph -> NodeSelector -> NodeSelector -> NodeSelector -> Triples Source # query :: RDF AlgebraicGraph -> Maybe Node -> Maybe Node -> Maybe Node -> Triples Source # | |
Rdf TList Source # | |
Defined in Data.RDF.Graph.TList Methods baseUrl :: RDF TList -> Maybe BaseUrl Source # prefixMappings :: RDF TList -> PrefixMappings Source # addPrefixMappings :: RDF TList -> PrefixMappings -> Bool -> RDF TList Source # mkRdf :: Triples -> Maybe BaseUrl -> PrefixMappings -> RDF TList Source # addTriple :: RDF TList -> Triple -> RDF TList Source # removeTriple :: RDF TList -> Triple -> RDF TList Source # triplesOf :: RDF TList -> Triples Source # uniqTriplesOf :: RDF TList -> Triples Source # select :: RDF TList -> NodeSelector -> NodeSelector -> NodeSelector -> Triples Source # query :: RDF TList -> Maybe Node -> Maybe Node -> Maybe Node -> Triples Source # |
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 NTriplesParser Source # |
|
Defined in Text.RDF.RDF4H.NTriplesParser Methods parseString :: Rdf a => NTriplesParser -> Text -> Either ParseFailure (RDF a) Source # parseFile :: Rdf a => NTriplesParser -> String -> IO (Either ParseFailure (RDF a)) Source # parseURL :: Rdf a => NTriplesParser -> String -> IO (Either ParseFailure (RDF a)) Source # | |
RdfParser NTriplesParserCustom Source # |
|
Defined in Text.RDF.RDF4H.NTriplesParser Methods parseString :: Rdf a => NTriplesParserCustom -> Text -> Either ParseFailure (RDF a) Source # parseFile :: Rdf a => NTriplesParserCustom -> String -> IO (Either ParseFailure (RDF a)) Source # parseURL :: Rdf a => NTriplesParserCustom -> String -> IO (Either ParseFailure (RDF a)) Source # | |
RdfParser TurtleParser Source # |
|
Defined in Text.RDF.RDF4H.TurtleParser Methods parseString :: Rdf a => TurtleParser -> Text -> Either ParseFailure (RDF a) Source # parseFile :: Rdf a => TurtleParser -> String -> IO (Either ParseFailure (RDF a)) Source # parseURL :: Rdf a => TurtleParser -> String -> IO (Either ParseFailure (RDF a)) Source # | |
RdfParser TurtleParserCustom Source # |
|
Defined in Text.RDF.RDF4H.TurtleParser Methods parseString :: Rdf a => TurtleParserCustom -> Text -> Either ParseFailure (RDF a) Source # parseFile :: Rdf a => TurtleParserCustom -> String -> IO (Either ParseFailure (RDF a)) Source # parseURL :: Rdf a => TurtleParserCustom -> String -> IO (Either ParseFailure (RDF a)) Source # | |
RdfParser XmlParser Source # | |
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 # | |
Defined in Text.RDF.RDF4H.NTriplesSerializer Methods hWriteRdf :: Rdf a => NTriplesSerializer -> Handle -> RDF a -> IO () Source # writeRdf :: Rdf a => NTriplesSerializer -> RDF a -> IO () Source # hWriteH :: Rdf a => NTriplesSerializer -> Handle -> RDF a -> IO () Source # writeH :: Rdf a => NTriplesSerializer -> RDF a -> IO () Source # hWriteTs :: NTriplesSerializer -> Handle -> Triples -> IO () Source # writeTs :: NTriplesSerializer -> Triples -> IO () Source # hWriteT :: NTriplesSerializer -> Handle -> Triple -> IO () Source # writeT :: NTriplesSerializer -> Triple -> IO () Source # hWriteN :: NTriplesSerializer -> Handle -> Node -> IO () Source # | |
RdfSerializer TurtleSerializer Source # | |
Defined in Text.RDF.RDF4H.TurtleSerializer Methods hWriteRdf :: Rdf a => TurtleSerializer -> Handle -> RDF a -> IO () Source # writeRdf :: Rdf a => TurtleSerializer -> RDF a -> IO () Source # hWriteH :: Rdf a => TurtleSerializer -> Handle -> RDF a -> IO () Source # writeH :: Rdf a => TurtleSerializer -> RDF a -> IO () Source # hWriteTs :: TurtleSerializer -> Handle -> Triples -> IO () Source # writeTs :: TurtleSerializer -> Triples -> IO () Source # hWriteT :: TurtleSerializer -> Handle -> Triple -> IO () Source # writeT :: TurtleSerializer -> Triple -> IO () Source # hWriteN :: TurtleSerializer -> Handle -> Node -> IO () Source # |
Namespaces and Prefixes
Represents a namespace as either a prefix and uri, respectively, or just a uri.
Constructors
PrefixedNS Text Text | |
PlainNS Text |
Instances
newtype PrefixMappings Source #
An alias for a map from prefix to namespace URI.
Constructors
PrefixMappings (Map Text Text) |
Instances
Monoid PrefixMappings Source # | |||||
Defined in Data.RDF.Types Methods mappend :: PrefixMappings -> PrefixMappings -> PrefixMappings # mconcat :: [PrefixMappings] -> PrefixMappings # | |||||
Semigroup PrefixMappings Source # | |||||
Defined in Data.RDF.Types Methods (<>) :: PrefixMappings -> PrefixMappings -> PrefixMappings # sconcat :: NonEmpty PrefixMappings -> PrefixMappings # stimes :: Integral b => b -> PrefixMappings -> PrefixMappings # | |||||
Generic PrefixMappings Source # | |||||
Defined in Data.RDF.Types Associated Types
Methods from :: PrefixMappings -> Rep PrefixMappings x # to :: Rep PrefixMappings x -> PrefixMappings # | |||||
Show PrefixMappings Source # | |||||
Defined in Data.RDF.Types Methods showsPrec :: Int -> PrefixMappings -> ShowS # show :: PrefixMappings -> String # showList :: [PrefixMappings] -> ShowS # | |||||
Binary PrefixMappings Source # | |||||
Defined in Data.RDF.Types Methods put :: PrefixMappings -> Put # get :: Get PrefixMappings # putList :: [PrefixMappings] -> Put # | |||||
NFData PrefixMappings Source # | |||||
Defined in Data.RDF.Types Methods rnf :: PrefixMappings -> () # | |||||
Eq PrefixMappings Source # | |||||
Defined in Data.RDF.Types Methods (==) :: PrefixMappings -> PrefixMappings -> Bool # (/=) :: PrefixMappings -> PrefixMappings -> Bool # | |||||
Ord PrefixMappings Source # | |||||
Defined in Data.RDF.Types Methods compare :: PrefixMappings -> PrefixMappings -> Ordering # (<) :: PrefixMappings -> PrefixMappings -> Bool # (<=) :: PrefixMappings -> PrefixMappings -> Bool # (>) :: PrefixMappings -> PrefixMappings -> Bool # (>=) :: PrefixMappings -> PrefixMappings -> Bool # max :: PrefixMappings -> PrefixMappings -> PrefixMappings # min :: PrefixMappings -> PrefixMappings -> PrefixMappings # | |||||
type Rep PrefixMappings Source # | |||||
Defined in Data.RDF.Types |
newtype PrefixMapping Source #
A mapping of a prefix to the URI for that prefix.
Constructors
PrefixMapping (Text, Text) |
Instances
Show PrefixMapping Source # | |
Defined in Data.RDF.Types Methods showsPrec :: Int -> PrefixMapping -> ShowS # show :: PrefixMapping -> String # showList :: [PrefixMapping] -> ShowS # | |
Eq PrefixMapping Source # | |
Defined in Data.RDF.Types Methods (==) :: PrefixMapping -> PrefixMapping -> Bool # (/=) :: PrefixMapping -> PrefixMapping -> Bool # | |
Ord PrefixMapping Source # | |
Defined in Data.RDF.Types Methods compare :: PrefixMapping -> PrefixMapping -> Ordering # (<) :: PrefixMapping -> PrefixMapping -> Bool # (<=) :: PrefixMapping -> PrefixMapping -> Bool # (>) :: PrefixMapping -> PrefixMapping -> Bool # (>=) :: PrefixMapping -> PrefixMapping -> Bool # max :: PrefixMapping -> PrefixMapping -> PrefixMapping # min :: PrefixMapping -> PrefixMapping -> PrefixMapping # |
Supporting types
The base URL of an RDF.
Instances
Monoid BaseUrl Source # | |||||
Semigroup BaseUrl Source # | |||||
Generic BaseUrl Source # | |||||
Defined in Data.RDF.Types Associated Types
| |||||
Show BaseUrl Source # | |||||
Binary BaseUrl Source # | |||||
NFData BaseUrl Source # | |||||
Defined in Data.RDF.Types | |||||
Eq BaseUrl Source # | |||||
Ord BaseUrl Source # | |||||
type Rep BaseUrl Source # | |||||
Defined in Data.RDF.Types |
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
Show ParseFailure Source # | |
Defined in Data.RDF.Types Methods showsPrec :: Int -> ParseFailure -> ShowS # show :: ParseFailure -> String # showList :: [ParseFailure] -> ShowS # | |
Eq ParseFailure Source # | |
Defined in Data.RDF.Types |