hsparql-0.3.2: A SPARQL query generator and DSL, and a client to query a SPARQL server.

Safe HaskellNone
LanguageHaskell98

Database.HSparql.QueryGenerator

Contents

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.

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 #

describeIRI :: IRIRef -> Query IRIRef 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.

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.

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

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

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.

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 Source #

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

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

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

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

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

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

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

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

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

(.>=.) :: (TermLike a, TermLike b) => a -> b -> Expr 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 Functions

str :: BuiltinFunc1 Source #

lang :: BuiltinFunc1 Source #

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 #

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 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 

type BlankNodePattern = [DynamicPredicateObject] Source #

data SelectQuery Source #

Constructors

SelectQuery 

Fields

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

TermLike Bool Source # 

Methods

varOrTerm :: Bool -> VarOrTerm Source #

expr :: Bool -> Expr Source #

TermLike Integer Source # 

Methods

varOrTerm :: Integer -> VarOrTerm Source #

expr :: Integer -> Expr Source #

TermLike Text Source # 

Methods

varOrTerm :: Text -> VarOrTerm Source #

expr :: Text -> Expr Source #

TermLike Node Source # 

Methods

varOrTerm :: Node -> VarOrTerm Source #

expr :: Node -> Expr Source #

TermLike VarOrNode Source # 

Methods

varOrTerm :: VarOrNode -> VarOrTerm Source #

expr :: VarOrNode -> Expr Source #

TermLike BlankNodePattern Source # 

Methods

varOrTerm :: BlankNodePattern -> VarOrTerm Source #

expr :: BlankNodePattern -> Expr Source #

TermLike Variable Source # 

Methods

varOrTerm :: Variable -> VarOrTerm Source #

expr :: Variable -> Expr Source #

TermLike (Text, Text) Source # 

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.

class TermLike a => PredicateTermLike a Source #

Restriction of TermLike to the role of predicate.