Copyright | Travis Whitaker 2016 |
---|---|
License | MIT |
Maintainer | pi.boy.travis@gmail.com |
Stability | Provisional |
Portability | Portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
This module provides types for representing RDF data based on the abstract syntax described in RDF 1.1 Concepts and Abstract Syntax.
Synopsis
- data RDFGraph = RDFGraph {
- rdfLabel :: !(Maybe IRI)
- rdfTriples :: [Triple]
- data Quad = Quad {
- quadTriple :: !Triple
- quadGraph :: !(Maybe IRI)
- data Triple = Triple !Subject !Predicate !Object
- data Subject
- newtype Predicate = Predicate {
- unPredicate :: IRI
- data Object
- newtype BlankNode = BlankNode {
- unBlankNode :: Text
- data Literal = Literal {
- litString :: !Text
- litType :: !LiteralType
- data LiteralType
- data IRI = IRI {}
- data IRIAuth = IRIAuth {}
Graphs
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.
RDFGraph | |
|
Instances
Generic RDFGraph Source # | |
Read RDFGraph Source # | |
Show RDFGraph Source # | |
NFData RDFGraph Source # | |
Defined in Data.RDF.Internal | |
Eq RDFGraph Source # | |
Ord RDFGraph Source # | |
Defined in Data.RDF.Internal | |
type Rep RDFGraph Source # | |
Defined in Data.RDF.Internal type Rep RDFGraph = D1 ('MetaData "RDFGraph" "Data.RDF.Internal" "rdf-0.1.0.7-KwPFeMtuF2mFgprU5G6Koq" '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]))) |
An RDF quad, i.e. a triple belonging to a named graph.
Instances
Generic Quad Source # | |
Read Quad Source # | |
Show Quad Source # | |
NFData Quad Source # | |
Defined in Data.RDF.Internal | |
Eq Quad Source # | |
Ord Quad Source # | |
type Rep Quad Source # | |
Defined in Data.RDF.Internal type Rep Quad = D1 ('MetaData "Quad" "Data.RDF.Internal" "rdf-0.1.0.7-KwPFeMtuF2mFgprU5G6Koq" '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)))) |
An RDF triple.
Instances
Generic Triple Source # | |
Read Triple Source # | |
Show Triple Source # | |
NFData Triple Source # | |
Defined in Data.RDF.Internal | |
Eq Triple Source # | |
Ord Triple Source # | |
type Rep Triple Source # | |
Defined in Data.RDF.Internal type Rep Triple = D1 ('MetaData "Triple" "Data.RDF.Internal" "rdf-0.1.0.7-KwPFeMtuF2mFgprU5G6Koq" 'False) (C1 ('MetaCons "Triple" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Subject) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Predicate) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Object)))) |
Triple Components
An RDF subject, i.e. either an IRI
or a BlankNode
.
This type has an IsString
instance, allowing string literals to be
interpreted as Subject
s with -XOverloadedStrings
, like so:
>>>
"<http://example.com> :: Subject
IRISubject (IRI (...))>>>
"_:some-node" :: Subject
BlankSubject (BlankNode {unBlankNode = "some-node"})
Instances
IsString Subject Source # | This instance uses |
Defined in Data.RDF.Internal fromString :: String -> Subject # | |
Generic Subject Source # | |
Read Subject Source # | |
Show Subject Source # | |
NFData Subject Source # | |
Defined in Data.RDF.Internal | |
Eq Subject Source # | |
Ord Subject Source # | |
type Rep Subject Source # | |
Defined in Data.RDF.Internal type Rep Subject = D1 ('MetaData "Subject" "Data.RDF.Internal" "rdf-0.1.0.7-KwPFeMtuF2mFgprU5G6Koq" '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))) |
An RDF predicate.
This type has an IsString
instance, allowing string literals to be
interpreted as Predicate
s with -XOverloadedStrings
, like so:
>>>
"<http://example.com>" :: Predicate
Predicate {unPredicate = IRI (...)}
Instances
IsString Predicate Source # | This instance uses |
Defined in Data.RDF.Internal fromString :: String -> Predicate # | |
Generic Predicate Source # | |
Read Predicate Source # | |
Show Predicate Source # | |
NFData Predicate Source # | |
Defined in Data.RDF.Internal | |
Eq Predicate Source # | |
Ord Predicate Source # | |
Defined in Data.RDF.Internal | |
type Rep Predicate Source # | |
Defined in Data.RDF.Internal |
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 Object
s 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
IsString Object Source # | This instance uses |
Defined in Data.RDF.Internal fromString :: String -> Object # | |
Generic Object Source # | |
Read Object Source # | |
Show Object Source # | |
NFData Object Source # | |
Defined in Data.RDF.Internal | |
Eq Object Source # | |
Ord Object Source # | |
type Rep Object Source # | |
Defined in Data.RDF.Internal type Rep Object = D1 ('MetaData "Object" "Data.RDF.Internal" "rdf-0.1.0.7-KwPFeMtuF2mFgprU5G6Koq" '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
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 BlankNode
s with -XOverloadedStrings
, like so:
>>>
"_:some-node" :: BlankNode
BlankNode {unBlankNode = "some-node"}
Instances
IsString BlankNode Source # | This instance uses |
Defined in Data.RDF.Internal fromString :: String -> BlankNode # | |
Generic BlankNode Source # | |
Read BlankNode Source # | |
Show BlankNode Source # | |
NFData BlankNode Source # | |
Defined in Data.RDF.Internal | |
Eq BlankNode Source # | |
Ord BlankNode Source # | |
Defined in Data.RDF.Internal | |
type Rep BlankNode Source # | |
Defined in Data.RDF.Internal |
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 Literal
s 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 (...)}
Literal | |
|
Instances
IsString Literal Source # | This instance uses |
Defined in Data.RDF.Internal fromString :: String -> Literal # | |
Generic Literal Source # | |
Read Literal Source # | |
Show Literal Source # | |
NFData Literal Source # | |
Defined in Data.RDF.Internal | |
Eq Literal Source # | |
Ord Literal Source # | |
type Rep Literal Source # | |
Defined in Data.RDF.Internal type Rep Literal = D1 ('MetaData "Literal" "Data.RDF.Internal" "rdf-0.1.0.7-KwPFeMtuF2mFgprU5G6Koq" '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
IRIs
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 IRI
s 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 }
IRI | |
|
Instances
IsString IRI Source # | This instance uses |
Defined in Data.RDF.Internal fromString :: String -> IRI # | |
Generic IRI Source # | |
Read IRI Source # | |
Show IRI Source # | |
NFData IRI Source # | |
Defined in Data.RDF.Internal | |
Eq IRI Source # | |
Ord IRI Source # | |
type Rep IRI Source # | |
Defined in Data.RDF.Internal type Rep IRI = D1 ('MetaData "IRI" "Data.RDF.Internal" "rdf-0.1.0.7-KwPFeMtuF2mFgprU5G6Koq" '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)))))) |
An IRI Authority, as described by RFC 3987.
Instances
Generic IRIAuth Source # | |
Read IRIAuth Source # | |
Show IRIAuth Source # | |
NFData IRIAuth Source # | |
Defined in Data.RDF.Internal | |
Eq IRIAuth Source # | |
Ord IRIAuth Source # | |
type Rep IRIAuth Source # | |
Defined in Data.RDF.Internal type Rep IRIAuth = D1 ('MetaData "IRIAuth" "Data.RDF.Internal" "rdf-0.1.0.7-KwPFeMtuF2mFgprU5G6Koq" '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))))) |