DSH-0.8.2.2: Database Supported Haskell

Safe HaskellNone

Database.DSH

Contents

Description

This module is intended to be imported qualified, to avoid name clashes with Prelude functions. For example:

 import qualified Database.DSH as Q
 import Database.DSH (Q)

Alternatively you can hide Prelude and import this module like this:

 import Prelude ()
 import Database.DSH

In this case you still get Prelude definitions that are not provided by Database.DSH.

Synopsis

Referring to persistent tables

table :: (QA a, TA a) => String -> Q [a]Source

tableDB :: (QA a, TA a) => String -> Q [a]Source

tableWithKeys :: (QA a, TA a) => String -> [[String]] -> Q [a]Source

tableCSV :: (QA a, TA a) => String -> Q [a]Source

toQ

toQ :: QA a => a -> Q aSource

Unit

Boolean logic

Equality and Ordering

eq :: (QA a, Eq a) => Q a -> Q a -> Q BoolSource

(==) :: (QA a, Eq a) => Q a -> Q a -> Q BoolSource

neq :: (QA a, Eq a) => Q a -> Q a -> Q BoolSource

(/=) :: (QA a, Eq a) => Q a -> Q a -> Q BoolSource

lt :: (QA a, Ord a) => Q a -> Q a -> Q BoolSource

(<) :: (QA a, Ord a) => Q a -> Q a -> Q BoolSource

lte :: (QA a, Ord a) => Q a -> Q a -> Q BoolSource

(<=) :: (QA a, Ord a) => Q a -> Q a -> Q BoolSource

gte :: (QA a, Ord a) => Q a -> Q a -> Q BoolSource

(>=) :: (QA a, Ord a) => Q a -> Q a -> Q BoolSource

gt :: (QA a, Ord a) => Q a -> Q a -> Q BoolSource

(>) :: (QA a, Ord a) => Q a -> Q a -> Q BoolSource

min :: (QA a, Ord a) => Q a -> Q a -> Q aSource

max :: (QA a, Ord a) => Q a -> Q a -> Q aSource

Conditionals

bool :: QA a => Q a -> Q a -> Q Bool -> Q aSource

cond :: QA a => Q Bool -> Q a -> Q a -> Q aSource

ifThenElse :: QA a => Q Bool -> Q a -> Q a -> Q aSource

(?) :: QA a => Q Bool -> (Q a, Q a) -> Q aSource

Maybe

listToMaybe :: QA a => Q [a] -> Q (Maybe a)Source

maybeToList :: QA a => Q (Maybe a) -> Q [a]Source

nothing :: QA a => Q (Maybe a)Source

just :: QA a => Q a -> Q (Maybe a)Source

isNothing :: QA a => Q (Maybe a) -> Q BoolSource

isJust :: QA a => Q (Maybe a) -> Q BoolSource

fromJust :: QA a => Q (Maybe a) -> Q aSource

maybe :: (QA a, QA b) => Q b -> (Q a -> Q b) -> Q (Maybe a) -> Q bSource

fromMaybe :: QA a => Q a -> Q (Maybe a) -> Q aSource

catMaybes :: QA a => Q [Maybe a] -> Q [a]Source

mapMaybe :: (QA a, QA b) => (Q a -> Q (Maybe b)) -> Q [a] -> Q [b]Source

Either

pairToEither :: (QA a, QA b) => Q ([a], [b]) -> Q (Either a b)Source

eitherToPair :: (QA a, QA b) => Q (Either a b) -> Q ([a], [b])Source

left :: (QA a, QA b) => Q a -> Q (Either a b)Source

right :: (QA a, QA b) => Q b -> Q (Either a b)Source

isLeft :: (QA a, QA b) => Q (Either a b) -> Q BoolSource

isRight :: (QA a, QA b) => Q (Either a b) -> Q BoolSource

either :: (QA a, QA b, QA c) => (Q a -> Q c) -> (Q b -> Q c) -> Q (Either a b) -> Q cSource

lefts :: (QA a, QA b) => Q [Either a b] -> Q [a]Source

rights :: (QA a, QA b) => Q [Either a b] -> Q [b]Source

partitionEithers :: (QA a, QA b) => Q [Either a b] -> Q ([a], [b])Source

List Construction

nil :: QA a => Q [a]Source

empty :: QA a => Q [a]Source

cons :: QA a => Q a -> Q [a] -> Q [a]Source

(<|) :: QA a => Q a -> Q [a] -> Q [a]Source

snoc :: QA a => Q [a] -> Q a -> Q [a]Source

(|>) :: QA a => Q [a] -> Q a -> Q [a]Source

singleton :: QA a => Q a -> Q [a]Source

List Operations

head :: QA a => Q [a] -> Q aSource

tail :: QA a => Q [a] -> Q [a]Source

take :: QA a => Q Integer -> Q [a] -> Q [a]Source

drop :: QA a => Q Integer -> Q [a] -> Q [a]Source

map :: (QA a, QA b) => (Q a -> Q b) -> Q [a] -> Q [b]Source

append :: QA a => Q [a] -> Q [a] -> Q [a]Source

(++) :: QA a => Q [a] -> Q [a] -> Q [a]Source

filter :: QA a => (Q a -> Q Bool) -> Q [a] -> Q [a]Source

groupWithKey :: (QA a, QA b, Ord b) => (Q a -> Q b) -> Q [a] -> Q [(b, [a])]Source

groupWith :: (QA a, QA b, Ord b) => (Q a -> Q b) -> Q [a] -> Q [[a]]Source

sortWith :: (QA a, QA b, Ord b) => (Q a -> Q b) -> Q [a] -> Q [a]Source

last :: QA a => Q [a] -> Q aSource

init :: QA a => Q [a] -> Q [a]Source

null :: QA a => Q [a] -> Q BoolSource

length :: QA a => Q [a] -> Q IntegerSource

index :: QA a => Q [a] -> Q Integer -> Q aSource

(!!) :: QA a => Q [a] -> Q Integer -> Q aSource

reverse :: QA a => Q [a] -> Q [a]Source

Special folds

or :: Q [Bool] -> Q BoolSource

any :: QA a => (Q a -> Q Bool) -> Q [a] -> Q BoolSource

all :: QA a => (Q a -> Q Bool) -> Q [a] -> Q BoolSource

sum :: (QA a, Num a) => Q [a] -> Q aSource

concat :: QA a => Q [[a]] -> Q [a]Source

concatMap :: (QA a, QA b) => (Q a -> Q [b]) -> Q [a] -> Q [b]Source

maximum :: (QA a, Ord a) => Q [a] -> Q aSource

minimum :: (QA a, Ord a) => Q [a] -> Q aSource

Sublists

splitAt :: QA a => Q Integer -> Q [a] -> Q ([a], [a])Source

takeWhile :: QA a => (Q a -> Q Bool) -> Q [a] -> Q [a]Source

dropWhile :: QA a => (Q a -> Q Bool) -> Q [a] -> Q [a]Source

span :: QA a => (Q a -> Q Bool) -> Q [a] -> Q ([a], [a])Source

break :: QA a => (Q a -> Q Bool) -> Q [a] -> Q ([a], [a])Source

Searching Lists

elem :: (QA a, Eq a) => Q a -> Q [a] -> Q BoolSource

notElem :: (QA a, Eq a) => Q a -> Q [a] -> Q BoolSource

lookup :: (QA a, QA b, Eq a) => Q a -> Q [(a, b)] -> Q (Maybe b)Source

Zipping and Unzipping Lists

zip :: (QA a, QA b) => Q [a] -> Q [b] -> Q [(a, b)]Source

zipWith :: (QA a, QA b, QA c) => (Q a -> Q b -> Q c) -> Q [a] -> Q [b] -> Q [c]Source

unzip :: (QA a, QA b) => Q [(a, b)] -> Q ([a], [b])Source

zip3 :: (QA a, QA b, QA c) => Q [a] -> Q [b] -> Q [c] -> Q [(a, b, c)]Source

zipWith3 :: (QA a, QA b, QA c, QA d) => (Q a -> Q b -> Q c -> Q d) -> Q [a] -> Q [b] -> Q [c] -> Q [d]Source

unzip3 :: (QA a, QA b, QA c) => Q [(a, b, c)] -> Q ([a], [b], [c])Source

Set-oriented operations

nub :: (QA a, Eq a) => Q [a] -> Q [a]Source

Tuple Projection Functions

fst :: (QA a, QA b) => Q (a, b) -> Q aSource

snd :: (QA a, QA b) => Q (a, b) -> Q bSource

Conversions between numeric types

Rebind Monadic Combinators

return :: QA a => Q a -> Q [a]Source

(>>=) :: (QA a, QA b) => Q [a] -> (Q a -> Q [b]) -> Q [b]Source

(>>) :: (QA a, QA b) => Q [a] -> Q [b] -> Q [b]Source

mzip :: (QA a, QA b) => Q [a] -> Q [b] -> Q [(a, b)]Source

guard :: Q Bool -> Q [()]Source

Construction of tuples

pair :: (QA a, QA b) => Q a -> Q b -> Q (a, b)Source

triple :: (QA a, QA b, QA c) => Q a -> Q b -> Q c -> Q (a, b, c)Source

tuple7 :: forall a b c d e f g. (QA a, QA b, QA c, QA d, QA e, QA f, QA g) => Q a -> Q b -> Q c -> Q d -> Q e -> Q f -> Q g -> Q ((,,,,,,) a b c d e f g)Source

tuple6 :: forall a b c d e f. (QA a, QA b, QA c, QA d, QA e, QA f) => Q a -> Q b -> Q c -> Q d -> Q e -> Q f -> Q ((,,,,,) a b c d e f)Source

tuple5 :: forall a b c d e. (QA a, QA b, QA c, QA d, QA e) => Q a -> Q b -> Q c -> Q d -> Q e -> Q ((,,,,) a b c d e)Source

tuple4 :: forall a b c d. (QA a, QA b, QA c, QA d) => Q a -> Q b -> Q c -> Q d -> Q ((,,,) a b c d)Source

tuple3 :: forall a b c. (QA a, QA b, QA c) => Q a -> Q b -> Q c -> Q ((,,) a b c)Source

tuple2 :: forall a b. (QA a, QA b) => Q a -> Q b -> Q ((,) a b)Source

Missing functions

 

This module offers most of the functions on lists given in PreludeList for the Q type. Missing functions are:

General folds:

 foldl
 foldl1
 scanl
 scanl1
 foldr
 foldr1
 scanr
 scanr1

Infinit lists:

 iterate
 repeat
 cycle

String functions:

 lines
 words
 unlines
 unwords

data Q a Source

Instances

Fractional (Q Double) 
Num (Q Double) 
Num (Q Integer) 
IsString (Q Text) 
View (Q Bool) 
View (Q Char) 
View (Q Double) 
View (Q Integer) 
View (Q ()) 
(QA a, QA b) => View (Q (a, b)) 
(QA a, QA b, QA c) => View (Q (a, b, c)) 
(QA a0, QA b0, QA c0, QA d0) => View (Q (a0, b0, c0, d0)) 
(QA a0, QA b0, QA c0, QA d0, QA e0) => View (Q (a0, b0, c0, d0, e0)) 
(QA a0, QA b0, QA c0, QA d0, QA e0, QA f0) => View (Q (a0, b0, c0, d0, e0, f0)) 
(QA a0, QA b0, QA c0, QA d0, QA e0, QA f0, QA g0) => View (Q (a0, b0, c0, d0, e0, f0, g0)) 
View (Q Text) 

class Reify (Rep a) => QA a Source

Instances

QA Bool 
QA Char 
QA Double 
QA Integer 
QA () 
QA Text 
(Reify (Rep [a]), QA a) => QA [a] 
(Reify (Rep (Maybe a)), QA a) => QA (Maybe a) 
(Reify (Rep (Either a b)), QA a, QA b) => QA (Either a b) 
(Reify (Rep (a, b)), QA a, QA b) => QA (a, b) 
(Reify (Rep (a, b, c)), QA a, QA b, QA c) => QA (a, b, c) 
(Reify (Rep (a0, b0, c0, d0)), QA a0, QA b0, QA c0, QA d0) => QA (a0, b0, c0, d0) 
(Reify (Rep (a0, b0, c0, d0, e0)), QA a0, QA b0, QA c0, QA d0, QA e0) => QA (a0, b0, c0, d0, e0) 
(Reify (Rep (a0, b0, c0, d0, e0, f0)), QA a0, QA b0, QA c0, QA d0, QA e0, QA f0) => QA (a0, b0, c0, d0, e0, f0) 
(Reify (Rep (a0, b0, c0, d0, e0, f0, g0)), QA a0, QA b0, QA c0, QA d0, QA e0, QA f0, QA g0) => QA (a0, b0, c0, d0, e0, f0, g0) 

class (QA a, QA r) => Elim a r whereSource

Methods

elim :: Q a -> Eliminator a rSource

Instances

(QA Bool, QA r) => Elim Bool r 
(QA Char, QA r) => Elim Char r 
(QA Double, QA r) => Elim Double r 
(QA Integer, QA r) => Elim Integer r 
(QA (), QA r) => Elim () r 
(QA Text, QA r) => Elim Text r 
(QA (Maybe a), QA a, QA r) => Elim (Maybe a) r 
(QA (Either a b), QA a, QA b, QA r) => Elim (Either a b) r 
(QA (a, b), QA a, QA b, QA r) => Elim (a, b) r 

class View a whereSource

Methods

view :: a -> ToView aSource

Instances

View (Q Bool) 
View (Q Char) 
View (Q Double) 
View (Q Integer) 
View (Q ()) 
(QA a, QA b) => View (Q (a, b)) 
(QA a, QA b, QA c) => View (Q (a, b, c)) 
(QA a0, QA b0, QA c0, QA d0) => View (Q (a0, b0, c0, d0)) 
(QA a0, QA b0, QA c0, QA d0, QA e0) => View (Q (a0, b0, c0, d0, e0)) 
(QA a0, QA b0, QA c0, QA d0, QA e0, QA f0) => View (Q (a0, b0, c0, d0, e0, f0)) 
(QA a0, QA b0, QA c0, QA d0, QA e0, QA f0, QA g0) => View (Q (a0, b0, c0, d0, e0, f0, g0)) 
View (Q Text) 

module Data.Text

module Prelude