hsparql-0.3.7: A SPARQL query generator and DSL, and a client to query a SPARQL server.
Safe HaskellNone
LanguageHaskell2010

Database.HSparql.QueryGenerator

Description

The query generator DSL for SPARQL, used when connecting to remote endpoints.

Synopsis

Creating Queries

createSelectQuery :: Query SelectQuery -> String Source #

Execute a 'Select Query' action, returning the String representation of the query.

createConstructQuery :: Query ConstructQuery -> String Source #

Execute a 'Construct Query' action, returning the String representation of the query.

createAskQuery :: Query AskQuery -> String Source #

Execute a 'Ask Query' action, returning the String representation of the query.

createUpdateQuery :: Query UpdateQuery -> String Source #

Execute a 'Update Query' action, returning the String representation of the query.

createDescribeQuery :: Query DescribeQuery -> String Source #

Execute a 'Describe Query' action, returning the String representation of the query.

Query Actions

prefix :: Text -> IRIRef -> Query Prefix Source #

Add a prefix to the query, given an IRI reference, and return it.

var :: Query Variable Source #

Create and return a variable to the query, usable in later expressions.

embeddedTriple :: (SubjectTermLike a, PredicateTermLike b, ObjectTermLike c) => a -> b -> c -> EmbeddedTriple Source #

Create an embedded triple usable in an expression. See SPARQL* at https://wiki.blazegraph.com/wiki/index.php/Reification_Done_Right or https://arxiv.org/abs/1406.3399.

triple :: (SubjectTermLike a, PredicateTermLike b, ObjectTermLike c) => a -> b -> c -> Query Pattern Source #

Restrict the query to only results for which values match constants in this triple, or for which the variables can be bound.

mkPredicateObject :: (PredicateTermLike a, ObjectTermLike b, QueryShow a, QueryShow b, Show a, Show b) => a -> b -> DynamicPredicateObject Source #

support for blank nodes.

Define a convenient alias for mkPredicateObject. Note: a pointfree definition leads to the monomorphism restriction (&) = mkPredicateObject. An example of its use:

p & o = mkPredicateObject p o

for example

q = do
  p <- prefix "" (iriRef "http://example.com/")
  s <- var
  o1 <- var
  o2 <- var
  _ <- triple s (p .:. "p1") [(p .:. "p2") & [(p .:. "p3") & o1], (p .:. "p4") & o2]
  return SelectQuery { queryVars = [s, o1] }
>>> createSelectQuery q
"PREFIX : <http://example.com/> SELECT  ?x0 ?x1 WHERE {?x0 :p1 [:p2 [:p3 ?x1]], [:p4 ?x2] .} "

describeIRI :: IRIRef -> Query IRIRef Source #

describeIRI_ :: IRIRef -> Query () Source #

optional :: Query a -> Query Pattern Source #

Add optional constraints on matches. Variable bindings within the optional action are lost, so variables must always be defined prior to opening the optional block.

service Source #

Arguments

:: IRIRef

SPARQL endpoint

-> Query a

SPARQL query to invoke against a remote SPARQL endpoint

-> Query Pattern 

Instruct a federated query processor to invoke the portion of a SPARQL query against a remote SPARQL endpoint.

For example

createQuery $ do
  foaf <- prefix "foaf" (iriRef "http://xmlns.com/foaf/0.1/")

  person    <- var
  name      <- var

  triple_ (iriRef "http://example.org/myfoaf/I") (foaf .:. "knows") person

  _ <- service (iriRef "http://people.example.org/sparql") $ do
    triple_ person (foaf .:. "name") name

  selectVars [name]

produces the SPARQL query:

PREFIX foaf: <http://xmlns.com/foaf/0.1/>
SELECT ?x1 WHERE {
  <http://example.org/myfoaf/I> foaf:knows ?x0 .
  SERVICE <http://people.example.org/sparql> {
    ?x0 foaf:name ?x1 .
  }
}

service_ :: IRIRef -> Query a -> Query () Source #

Same as service, but without returning the query patterns.

union :: Query a -> Query b -> Query Pattern Source #

Add a union structure to the query pattern. As with optional blocks, variables must be defined prior to the opening of any block.

union_ :: Query a -> Query b -> Query () Source #

filterExpr :: TermLike a => a -> Query Pattern Source #

Restrict results to only those for which the given expression is true.

bind :: Expr -> Variable -> Query Pattern Source #

Bind the result of an expression to a variable.

bind_ :: Expr -> Variable -> Query () Source #

subQuery :: Query SelectQuery -> Query Pattern Source #

Perform a subquery.

as :: Expr -> Variable -> SelectExpr Source #

Property paths

SPARQL 1.1 property paths documentation: https://www.w3.org/TR/sparql11-query/#propertypaths

a :: PathLengthOne Source #

Variable "a" representing the rdf:type property.

Binary operators

Property path binary operators

(.//.) :: (PropertyPathExprLike a, PropertyPathExprLike b) => a -> b -> PropertyPathExpr infixl 5 Source #

Creating a property path sequence.

>>> IRIRef "rdf:type" ./. IRIRef "rdfs:subClassOf" ./. IRIRef "rdfs:subClassOf"
rdf:type/rdfs:subClassOf/rdfs:subClassOf

(.|.) :: (PropertyPathExprLike a, PropertyPathExprLike b) => a -> b -> PropertyPathExpr infixl 4 Source #

Creating an alternative property path.

>>> IRIRef "rdfs:label" .|. IRIRef "foaf:name" .|. IRIRef "foaf:givenName
rdfs:label|foaf:name|foaf:givenName

Negative property set binary operators

(..|..) :: (NegativePropertySetLike a, NegativePropertySetLike b) => a -> b -> NegativePropertySet infixl 4 Source #

Creating an alternative property path inside a negative property set.

>>> neg $ IRIRef "rdfs:label" ..|.. IRIRef "foaf:name" ..|.. IRIRef "foaf:givenName"
!(rdfs:label|foaf:name|foaf:givenName)

Unary operators

Property path unary operators

inv :: PropertyPathExprLike a => a -> PropertyPathExpr Source #

Creating an inverse property path.

>>> inv (IRIRef "foaf:mbox")
^foaf:mbox

(*.) :: PropertyPathExprLike a => a -> PropertyPathExpr Source #

Creating a zero or more path.

>>> IRIRef "rdf:type" ./. ((IRIRef "rdfs:subClassOf") *.)
rdf:type/rdfs:subClassOf*

(+.) :: PropertyPathExprLike a => a -> PropertyPathExpr Source #

Creating a one or more path.

>>> ((IRIRef "foaf:knows") +.) ./. IRIRef "foaf:name"
foaf:knows+/foaf:name

(?.) :: PropertyPathExprLike a => a -> PropertyPathExpr Source #

Creating a zero or one path.

>>> rdfType ./. (rdfsSubClassOf ?.)
rdf:type/rdfs:subClassOf?

Negative property set unary operators

neg :: NegativePropertySet -> PropertyPathExpr Source #

Creating a negative property set.

>>> inv foafMbox
^foaf:mbox

inv' :: NegativePropertySetLike a => a -> NegativePropertySet Source #

Creating an inverse path of length one inside a negative property set.

>>> neg $ IRIRef "rdfs:label" ..|.. IRIRef "foaf:name" ..|.. (inv' $ IRIRef "foaf:givenName")
!(rdfs:label|foaf:name|^foaf:givenName)

Duplicate handling

distinct :: Query Duplicates Source #

Set duplicate handling to Distinct. By default, there are no reductions.

reduced :: Query Duplicates Source #

Set duplicate handling to Reduced. By default, there are no reductions.

Limit handling

limit :: Int -> Query Limit Source #

Set limit handling to the given value. By default, there are no limits. Note: negative numbers cause no query results to be returned.

Groups handling

groupBy :: TermLike a => a -> Query [GroupBy] Source #

Divide the solution into one or more groups.

groupBy_ :: TermLike a => a -> Query () Source #

Order handling

orderNext :: TermLike a => a -> Query () Source #

Alias of orderNextAsc.

orderNextAsc :: TermLike a => a -> Query () Source #

Order the results, after any previous ordering, based on the term, in ascending order.

orderNextDesc :: TermLike a => a -> Query () Source #

Order the results, after any previous ordering, based on the term, in descending order.

Auxiliary

(.:.) :: Prefix -> Text -> IRIRef Source #

Form a Node, with the Prefix and reference name.

iriRef :: Text -> IRIRef Source #

Term Manipulation

Operations

(.+.) :: (TermLike a, TermLike b) => a -> b -> Expr infixl 6 Source #

Add two terms.

(.-.) :: (TermLike a, TermLike b) => a -> b -> Expr infixl 6 Source #

Find the difference between two terms.

(.*.) :: (TermLike a, TermLike b) => a -> b -> Expr infixl 7 Source #

Multiply two terms.

(./.) :: (TermLike a, TermLike b) => a -> b -> Expr infixl 7 Source #

Divide two terms.

(.&&.) :: (TermLike a, TermLike b) => a -> b -> Expr infixr 3 Source #

Combine two boolean terms with AND

(.||.) :: (TermLike a, TermLike b) => a -> b -> Expr infixr 2 Source #

Combine two boolean terms with OR

Relations

(.==.) :: (TermLike a, TermLike b) => a -> b -> Expr infix 4 Source #

Create an expression which tests the relationship of the two operands, evaluating their equivalence.

(.!=.) :: (TermLike a, TermLike b) => a -> b -> Expr infix 4 Source #

Create an expression which tests the relationship of the two operands, evaluating their equivalence.

(.<.) :: (TermLike a, TermLike b) => a -> b -> Expr infix 4 Source #

Create an expression which tests the relationship of the two operands, evaluating their relative value.

(.>.) :: (TermLike a, TermLike b) => a -> b -> Expr infix 4 Source #

Create an expression which tests the relationship of the two operands, evaluating their relative value.

(.<=.) :: (TermLike a, TermLike b) => a -> b -> Expr infix 4 Source #

Create an expression which tests the relationship of the two operands, evaluating their relative value.

(.>=.) :: (TermLike a, TermLike b) => a -> b -> Expr infix 4 Source #

Create an expression which tests the relationship of the two operands, evaluating their relative value.

Negation

notExpr :: TermLike a => a -> Expr Source #

Negate any term-like expression, for use, e.g., in filtering.

Builtin aggregation functions

count :: BuiltinFunc1 Source #

Aggregate by count

sum_ :: BuiltinFunc1 Source #

Aggregate by sum

min_ :: BuiltinFunc1 Source #

Aggregate by minimum value

max_ :: BuiltinFunc1 Source #

Aggregate by maximum value

avg :: BuiltinFunc1 Source #

Aggregate by average

groupConcat :: TermLike a => a -> String -> Expr Source #

Aggregate a column by string concatenation with a separator.

Builtin Functions

str :: BuiltinFunc1 Source #

Cast as a string

lang :: BuiltinFunc1 Source #

Get the language of this element

langMatches :: BuiltinFunc2 Source #

datatype :: BuiltinFunc1 Source #

bound :: Variable -> Expr Source #

sameTerm :: BuiltinFunc2 Source #

isIRI :: BuiltinFunc1 Source #

isURI :: BuiltinFunc1 Source #

isBlank :: BuiltinFunc1 Source #

isLiteral :: BuiltinFunc1 Source #

regex :: BuiltinFunc2 Source #

regexOpts :: BuiltinFunc3 Source #

strlen :: BuiltinFunc1 Source #

strlen ( string ) - get the length of a string

substr :: BuiltinFunc1 Source #

substr ( string beginPosition stringLength ) - get a substring

ucase :: BuiltinFunc1 Source #

ucase ( string ) - convert to upper case

lcase :: BuiltinFunc1 Source #

lcase ( string ) - convert to lower case

strstarts :: BuiltinFunc2 Source #

strstarts ( string x ) - return true if x matches the beginning of string

strends :: BuiltinFunc2 Source #

strends ( string x ) - return true if x matches the end of string

contains :: BuiltinFunc2 Source #

contains ( string x ) - return true if x matches anywhere in string

strbefore :: BuiltinFunc2 Source #

strbefore ( string x ) - return the string preceding a match to x

strafter :: BuiltinFunc2 Source #

strafter ( string x ) - return the string after a match to x

abs_ :: BuiltinFunc1 Source #

abs_ ( x ) - take the absolute value of number x

round_ :: BuiltinFunc1 Source #

round ( x ) - round x to the nearest integer

ceil :: BuiltinFunc1 Source #

ceil ( number ) - round x up to the nearest integer

floor_ :: BuiltinFunc1 Source #

floor ( number ) - round x down to the nearest integer

concat_ :: BuiltinFunc2 Source #

concat_ ( x y ) - concatenate strings x and y

replace :: BuiltinFunc3 Source #

replace ( string p r ) - replace literal p with literal r in string

rand :: BuiltinFunc0 Source #

rand ( ) - produce a random number between 0 and 1

Printing Queries

qshow :: QueryShow a => a -> String Source #

Convert most query-related types to a String, most importantly QueryDatas.

Types

type Query a = State QueryData a Source #

The State monad applied to QueryData.

data Prefix Source #

Instances

Instances details
Eq Prefix Source # 
Instance details

Defined in Database.HSparql.QueryGenerator

Methods

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

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

Show Prefix Source # 
Instance details

Defined in Database.HSparql.QueryGenerator

data Variable Source #

Instances

Instances details
Show Variable Source # 
Instance details

Defined in Database.HSparql.QueryGenerator

ObjectTermLike Variable Source # 
Instance details

Defined in Database.HSparql.QueryGenerator

PredicateTermLike Variable Source # 
Instance details

Defined in Database.HSparql.QueryGenerator

SubjectTermLike Variable Source # 
Instance details

Defined in Database.HSparql.QueryGenerator

TermLike Variable Source # 
Instance details

Defined in Database.HSparql.QueryGenerator

Methods

varOrTerm :: Variable -> VarOrTerm Source #

expr :: Variable -> Expr Source #

data VarOrNode Source #

Enables programmatic construction of triples where it is not known in advance which parts of the triple will be variables and which will be Nodes.

Constructors

Var' Variable 
RDFNode Node 

Instances

Instances details
Show VarOrNode Source # 
Instance details

Defined in Database.HSparql.QueryGenerator

ObjectTermLike VarOrNode Source # 
Instance details

Defined in Database.HSparql.QueryGenerator

TermLike VarOrNode Source # 
Instance details

Defined in Database.HSparql.QueryGenerator

Methods

varOrTerm :: VarOrNode -> VarOrTerm Source #

expr :: VarOrNode -> Expr Source #

type BlankNodePattern = [DynamicPredicateObject] Source #

data Pattern Source #

Instances

Instances details
Show Pattern Source # 
Instance details

Defined in Database.HSparql.QueryGenerator

data SelectQuery Source #

Constructors

SelectQuery 

Fields

data SelectExpr Source #

Instances

Instances details
Show SelectExpr Source # 
Instance details

Defined in Database.HSparql.QueryGenerator

data AskQuery Source #

Constructors

AskQuery 

Fields

data UpdateQuery Source #

Constructors

UpdateQuery 

Fields

data DescribeQuery Source #

Constructors

DescribeQuery 

Fields

Classes

class TermLike a where Source #

Permit variables and values to seemlessly be put into argument for triple and similar functions

Minimal complete definition

varOrTerm

Methods

varOrTerm :: a -> VarOrTerm Source #

expr :: a -> Expr Source #

Instances

Instances details
TermLike Bool Source # 
Instance details

Defined in Database.HSparql.QueryGenerator

Methods

varOrTerm :: Bool -> VarOrTerm Source #

expr :: Bool -> Expr Source #

TermLike Integer Source # 
Instance details

Defined in Database.HSparql.QueryGenerator

Methods

varOrTerm :: Integer -> VarOrTerm Source #

expr :: Integer -> Expr Source #

TermLike Text Source # 
Instance details

Defined in Database.HSparql.QueryGenerator

Methods

varOrTerm :: Text -> VarOrTerm Source #

expr :: Text -> Expr Source #

TermLike Node Source # 
Instance details

Defined in Database.HSparql.QueryGenerator

Methods

varOrTerm :: Node -> VarOrTerm Source #

expr :: Node -> Expr Source #

TermLike VarOrNode Source # 
Instance details

Defined in Database.HSparql.QueryGenerator

Methods

varOrTerm :: VarOrNode -> VarOrTerm Source #

expr :: VarOrNode -> Expr Source #

TermLike BlankNodePattern Source # 
Instance details

Defined in Database.HSparql.QueryGenerator

Methods

varOrTerm :: BlankNodePattern -> VarOrTerm Source #

expr :: BlankNodePattern -> Expr Source #

TermLike Variable Source # 
Instance details

Defined in Database.HSparql.QueryGenerator

Methods

varOrTerm :: Variable -> VarOrTerm Source #

expr :: Variable -> Expr Source #

TermLike (Text, Text) Source # 
Instance details

Defined in Database.HSparql.QueryGenerator

Methods

varOrTerm :: (Text, Text) -> VarOrTerm Source #

expr :: (Text, Text) -> Expr Source #

class TermLike a => SubjectTermLike a Source #

Restriction of TermLike to the role of subject.

Instances

Instances details
SubjectTermLike BlankNodePattern Source # 
Instance details

Defined in Database.HSparql.QueryGenerator

SubjectTermLike Variable Source # 
Instance details

Defined in Database.HSparql.QueryGenerator

class TermLike a => PredicateTermLike a Source #

Restriction of TermLike to the role of predicate.

Instances

Instances details
PredicateTermLike Variable Source # 
Instance details

Defined in Database.HSparql.QueryGenerator

class TermLike a => ObjectTermLike a Source #

Restriction of TermLike to the role of object.