queryparser-0.1.0.1: Analysis and parsing library for SQL queries.

Safe HaskellNone
LanguageHaskell2010

Database.Sql.Type.Query

Documentation

data Query r a Source #

Constructors

QuerySelect a (Select r a) 
QueryExcept a (ComposedQueryColumns r a) (Query r a) (Query r a) 
QueryUnion a Distinct (ComposedQueryColumns r a) (Query r a) (Query r a) 
QueryIntersect a (ComposedQueryColumns r a) (Query r a) (Query r a) 
QueryWith a [CTE r a] (Query r a) 
QueryOrder a [Order r a] (Query r a) 
QueryLimit a (Limit a) (Query r a) 
QueryOffset a (Offset a) (Query r a) 

Instances

Evaluation e => Evaluate e (Query ResolvedNames Range) Source # 
ConstrainSASNames Functor r => Functor (Query r) Source # 

Methods

fmap :: (a -> b) -> Query r a -> Query r b #

(<$) :: a -> Query r b -> Query r a #

ConstrainSASNames Foldable r => Foldable (Query r) Source # 

Methods

fold :: Monoid m => Query r m -> m #

foldMap :: Monoid m => (a -> m) -> Query r a -> m #

foldr :: (a -> b -> b) -> b -> Query r a -> b #

foldr' :: (a -> b -> b) -> b -> Query r a -> b #

foldl :: (b -> a -> b) -> b -> Query r a -> b #

foldl' :: (b -> a -> b) -> b -> Query r a -> b #

foldr1 :: (a -> a -> a) -> Query r a -> a #

foldl1 :: (a -> a -> a) -> Query r a -> a #

toList :: Query r a -> [a] #

null :: Query r a -> Bool #

length :: Query r a -> Int #

elem :: Eq a => a -> Query r a -> Bool #

maximum :: Ord a => Query r a -> a #

minimum :: Ord a => Query r a -> a #

sum :: Num a => Query r a -> a #

product :: Num a => Query r a -> a #

ConstrainSASNames Traversable r => Traversable (Query r) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Query r a -> f (Query r b) #

sequenceA :: Applicative f => Query r (f a) -> f (Query r a) #

mapM :: Monad m => (a -> m b) -> Query r a -> m (Query r b) #

sequence :: Monad m => Query r (m a) -> m (Query r a) #

ConstrainSNames Eq r a => Eq (Query r a) Source # 

Methods

(==) :: Query r a -> Query r a -> Bool #

(/=) :: Query r a -> Query r a -> Bool #

(ConstrainSNames Data r a, Data r) => Data (Query r a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Query r a -> c (Query r a) #

gunfold :: (forall b c. Data b => c (b -> c) -> c c) -> (forall b. b -> c b) -> Constr -> c (Query r a) #

toConstr :: Query r a -> Constr #

dataTypeOf :: Query r a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Query r a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Query r a)) #

gmapT :: (forall b. Data b => b -> b) -> Query r a -> Query r a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Query r a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Query r a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Query r a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Query r a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Query r a -> m (Query r a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Query r a -> m (Query r a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Query r a -> m (Query r a) #

ConstrainSNames Ord r a => Ord (Query r a) Source # 

Methods

compare :: Query r a -> Query r a -> Ordering #

(<) :: Query r a -> Query r a -> Bool #

(<=) :: Query r a -> Query r a -> Bool #

(>) :: Query r a -> Query r a -> Bool #

(>=) :: Query r a -> Query r a -> Bool #

max :: Query r a -> Query r a -> Query r a #

min :: Query r a -> Query r a -> Query r a #

ConstrainSNames Show r a => Show (Query r a) Source # 

Methods

showsPrec :: Int -> Query r a -> ShowS #

show :: Query r a -> String #

showList :: [Query r a] -> ShowS #

Generic (Query r a) Source # 

Associated Types

type Rep (Query r a) :: * -> * #

Methods

from :: Query r a -> Rep (Query r a) x #

to :: Rep (Query r a) x -> Query r a #

ConstrainSNames ToJSON r a => ToJSON (Query r a) Source # 

Methods

toJSON :: Query r a -> Value #

toEncoding :: Query r a -> Encoding #

toJSONList :: [Query r a] -> Value #

toEncodingList :: [Query r a] -> Encoding #

ConstrainSNames FromJSON r a => FromJSON (Query r a) Source # 

Methods

parseJSON :: Value -> Parser (Query r a) #

parseJSONList :: Value -> Parser [Query r a] #

HasTables (Query ResolvedNames a) Source # 
HasColumns (Query ResolvedNames a) Source # 

Methods

goColumns :: Query ResolvedNames a -> Observer Source #

HasInfo (Query r a) Source # 

Associated Types

type Info (Query r a) :: * Source #

Methods

getInfo :: Query r a -> Info (Query r a) Source #

type EvalResult e (Query ResolvedNames Range) Source # 
type Rep (Query r a) Source # 
type Rep (Query r a) = D1 * (MetaData "Query" "Database.Sql.Type.Query" "queryparser-0.1.0.1-L3r1ujeH5Ss7CLthXKM008" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "QuerySelect" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Select r a))))) (C1 * (MetaCons "QueryExcept" PrefixI False) ((:*:) * ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (ComposedQueryColumns r a)))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Query r a))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Query r a))))))) ((:+:) * (C1 * (MetaCons "QueryUnion" PrefixI False) ((:*:) * ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Distinct))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (ComposedQueryColumns r a))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Query r a))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Query r a))))))) (C1 * (MetaCons "QueryIntersect" PrefixI False) ((:*:) * ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (ComposedQueryColumns r a)))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Query r a))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Query r a)))))))) ((:+:) * ((:+:) * (C1 * (MetaCons "QueryWith" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [CTE r a])) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Query r a)))))) (C1 * (MetaCons "QueryOrder" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Order r a])) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Query r a))))))) ((:+:) * (C1 * (MetaCons "QueryLimit" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Limit a))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Query r a)))))) (C1 * (MetaCons "QueryOffset" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Offset a))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Query r a)))))))))
type Info (Query r a) Source # 
type Info (Query r a) = a

newtype Distinct Source #

Constructors

Distinct Bool 

Instances

Eq Distinct Source # 
Data Distinct Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Distinct -> c Distinct #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Distinct #

toConstr :: Distinct -> Constr #

dataTypeOf :: Distinct -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Distinct) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Distinct) #

gmapT :: (forall b. Data b => b -> b) -> Distinct -> Distinct #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Distinct -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Distinct -> r #

gmapQ :: (forall d. Data d => d -> u) -> Distinct -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Distinct -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Distinct -> m Distinct #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Distinct -> m Distinct #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Distinct -> m Distinct #

Ord Distinct Source # 
Show Distinct Source # 
Generic Distinct Source # 

Associated Types

type Rep Distinct :: * -> * #

Methods

from :: Distinct -> Rep Distinct x #

to :: Rep Distinct x -> Distinct #

Arbitrary Distinct Source # 
ToJSON Distinct Source # 
FromJSON Distinct Source # 
type Rep Distinct Source # 
type Rep Distinct = D1 * (MetaData "Distinct" "Database.Sql.Type.Query" "queryparser-0.1.0.1-L3r1ujeH5Ss7CLthXKM008" True) (C1 * (MetaCons "Distinct" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)))

data CTE r a Source #

Constructors

CTE 

Fields

Instances

ConstrainSASNames Functor r => Functor (CTE r) Source # 

Methods

fmap :: (a -> b) -> CTE r a -> CTE r b #

(<$) :: a -> CTE r b -> CTE r a #

ConstrainSASNames Foldable r => Foldable (CTE r) Source # 

Methods

fold :: Monoid m => CTE r m -> m #

foldMap :: Monoid m => (a -> m) -> CTE r a -> m #

foldr :: (a -> b -> b) -> b -> CTE r a -> b #

foldr' :: (a -> b -> b) -> b -> CTE r a -> b #

foldl :: (b -> a -> b) -> b -> CTE r a -> b #

foldl' :: (b -> a -> b) -> b -> CTE r a -> b #

foldr1 :: (a -> a -> a) -> CTE r a -> a #

foldl1 :: (a -> a -> a) -> CTE r a -> a #

toList :: CTE r a -> [a] #

null :: CTE r a -> Bool #

length :: CTE r a -> Int #

elem :: Eq a => a -> CTE r a -> Bool #

maximum :: Ord a => CTE r a -> a #

minimum :: Ord a => CTE r a -> a #

sum :: Num a => CTE r a -> a #

product :: Num a => CTE r a -> a #

ConstrainSASNames Traversable r => Traversable (CTE r) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> CTE r a -> f (CTE r b) #

sequenceA :: Applicative f => CTE r (f a) -> f (CTE r a) #

mapM :: Monad m => (a -> m b) -> CTE r a -> m (CTE r b) #

sequence :: Monad m => CTE r (m a) -> m (CTE r a) #

ConstrainSNames Eq r a => Eq (CTE r a) Source # 

Methods

(==) :: CTE r a -> CTE r a -> Bool #

(/=) :: CTE r a -> CTE r a -> Bool #

(ConstrainSNames Data r a, Data r) => Data (CTE r a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CTE r a -> c (CTE r a) #

gunfold :: (forall b c. Data b => c (b -> c) -> c c) -> (forall b. b -> c b) -> Constr -> c (CTE r a) #

toConstr :: CTE r a -> Constr #

dataTypeOf :: CTE r a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (CTE r a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (CTE r a)) #

gmapT :: (forall b. Data b => b -> b) -> CTE r a -> CTE r a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CTE r a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CTE r a -> r #

gmapQ :: (forall d. Data d => d -> u) -> CTE r a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CTE r a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CTE r a -> m (CTE r a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CTE r a -> m (CTE r a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CTE r a -> m (CTE r a) #

ConstrainSNames Ord r a => Ord (CTE r a) Source # 

Methods

compare :: CTE r a -> CTE r a -> Ordering #

(<) :: CTE r a -> CTE r a -> Bool #

(<=) :: CTE r a -> CTE r a -> Bool #

(>) :: CTE r a -> CTE r a -> Bool #

(>=) :: CTE r a -> CTE r a -> Bool #

max :: CTE r a -> CTE r a -> CTE r a #

min :: CTE r a -> CTE r a -> CTE r a #

ConstrainSNames Show r a => Show (CTE r a) Source # 

Methods

showsPrec :: Int -> CTE r a -> ShowS #

show :: CTE r a -> String #

showList :: [CTE r a] -> ShowS #

Generic (CTE r a) Source # 

Associated Types

type Rep (CTE r a) :: * -> * #

Methods

from :: CTE r a -> Rep (CTE r a) x #

to :: Rep (CTE r a) x -> CTE r a #

ConstrainSNames ToJSON r a => ToJSON (CTE r a) Source # 

Methods

toJSON :: CTE r a -> Value #

toEncoding :: CTE r a -> Encoding #

toJSONList :: [CTE r a] -> Value #

toEncodingList :: [CTE r a] -> Encoding #

ConstrainSNames FromJSON r a => FromJSON (CTE r a) Source # 

Methods

parseJSON :: Value -> Parser (CTE r a) #

parseJSONList :: Value -> Parser [CTE r a] #

HasColumns (CTE ResolvedNames a) Source # 

Methods

goColumns :: CTE ResolvedNames a -> Observer Source #

type Rep (CTE r a) Source # 
type Rep (CTE r a) = D1 * (MetaData "CTE" "Database.Sql.Type.Query" "queryparser-0.1.0.1-L3r1ujeH5Ss7CLthXKM008" False) (C1 * (MetaCons "CTE" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "cteInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Just Symbol "cteAlias") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (TableAlias a)))) ((:*:) * (S1 * (MetaSel (Just Symbol "cteColumns") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ColumnAlias a])) (S1 * (MetaSel (Just Symbol "cteQuery") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Query r a))))))

data Select r a Source #

Instances

Evaluation e => Evaluate e (Select ResolvedNames Range) Source # 
ConstrainSASNames Functor r => Functor (Select r) Source # 

Methods

fmap :: (a -> b) -> Select r a -> Select r b #

(<$) :: a -> Select r b -> Select r a #

ConstrainSASNames Foldable r => Foldable (Select r) Source # 

Methods

fold :: Monoid m => Select r m -> m #

foldMap :: Monoid m => (a -> m) -> Select r a -> m #

foldr :: (a -> b -> b) -> b -> Select r a -> b #

foldr' :: (a -> b -> b) -> b -> Select r a -> b #

foldl :: (b -> a -> b) -> b -> Select r a -> b #

foldl' :: (b -> a -> b) -> b -> Select r a -> b #

foldr1 :: (a -> a -> a) -> Select r a -> a #

foldl1 :: (a -> a -> a) -> Select r a -> a #

toList :: Select r a -> [a] #

null :: Select r a -> Bool #

length :: Select r a -> Int #

elem :: Eq a => a -> Select r a -> Bool #

maximum :: Ord a => Select r a -> a #

minimum :: Ord a => Select r a -> a #

sum :: Num a => Select r a -> a #

product :: Num a => Select r a -> a #

ConstrainSASNames Traversable r => Traversable (Select r) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Select r a -> f (Select r b) #

sequenceA :: Applicative f => Select r (f a) -> f (Select r a) #

mapM :: Monad m => (a -> m b) -> Select r a -> m (Select r b) #

sequence :: Monad m => Select r (m a) -> m (Select r a) #

ConstrainSNames Eq r a => Eq (Select r a) Source # 

Methods

(==) :: Select r a -> Select r a -> Bool #

(/=) :: Select r a -> Select r a -> Bool #

(ConstrainSNames Data r a, Data r) => Data (Select r a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Select r a -> c (Select r a) #

gunfold :: (forall b c. Data b => c (b -> c) -> c c) -> (forall b. b -> c b) -> Constr -> c (Select r a) #

toConstr :: Select r a -> Constr #

dataTypeOf :: Select r a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Select r a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Select r a)) #

gmapT :: (forall b. Data b => b -> b) -> Select r a -> Select r a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Select r a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Select r a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Select r a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Select r a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Select r a -> m (Select r a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Select r a -> m (Select r a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Select r a -> m (Select r a) #

ConstrainSNames Ord r a => Ord (Select r a) Source # 

Methods

compare :: Select r a -> Select r a -> Ordering #

(<) :: Select r a -> Select r a -> Bool #

(<=) :: Select r a -> Select r a -> Bool #

(>) :: Select r a -> Select r a -> Bool #

(>=) :: Select r a -> Select r a -> Bool #

max :: Select r a -> Select r a -> Select r a #

min :: Select r a -> Select r a -> Select r a #

ConstrainSNames Show r a => Show (Select r a) Source # 

Methods

showsPrec :: Int -> Select r a -> ShowS #

show :: Select r a -> String #

showList :: [Select r a] -> ShowS #

Generic (Select r a) Source # 

Associated Types

type Rep (Select r a) :: * -> * #

Methods

from :: Select r a -> Rep (Select r a) x #

to :: Rep (Select r a) x -> Select r a #

ConstrainSNames ToJSON r a => ToJSON (Select r a) Source # 

Methods

toJSON :: Select r a -> Value #

toEncoding :: Select r a -> Encoding #

toJSONList :: [Select r a] -> Value #

toEncodingList :: [Select r a] -> Encoding #

ConstrainSNames FromJSON r a => FromJSON (Select r a) Source # 

Methods

parseJSON :: Value -> Parser (Select r a) #

parseJSONList :: Value -> Parser [Select r a] #

HasTables (Select ResolvedNames a) Source # 
HasColumns (Select ResolvedNames a) Source # 

Methods

goColumns :: Select ResolvedNames a -> Observer Source #

HasInfo (Select r a) Source # 

Associated Types

type Info (Select r a) :: * Source #

Methods

getInfo :: Select r a -> Info (Select r a) Source #

type EvalResult e (Select ResolvedNames Range) Source # 
type Rep (Select r a) Source # 
type Info (Select r a) Source # 
type Info (Select r a) = a

data SelectColumns r a Source #

Constructors

SelectColumns 

Instances

Evaluation e => Evaluate e (SelectColumns ResolvedNames Range) Source #

SelectColumns tells us how to map from the records provided by the FROM to (unfiltered, &c) records provided by our select. Evaluating it gives us that function.

ConstrainSASNames Functor r => Functor (SelectColumns r) Source # 

Methods

fmap :: (a -> b) -> SelectColumns r a -> SelectColumns r b #

(<$) :: a -> SelectColumns r b -> SelectColumns r a #

ConstrainSASNames Foldable r => Foldable (SelectColumns r) Source # 

Methods

fold :: Monoid m => SelectColumns r m -> m #

foldMap :: Monoid m => (a -> m) -> SelectColumns r a -> m #

foldr :: (a -> b -> b) -> b -> SelectColumns r a -> b #

foldr' :: (a -> b -> b) -> b -> SelectColumns r a -> b #

foldl :: (b -> a -> b) -> b -> SelectColumns r a -> b #

foldl' :: (b -> a -> b) -> b -> SelectColumns r a -> b #

foldr1 :: (a -> a -> a) -> SelectColumns r a -> a #

foldl1 :: (a -> a -> a) -> SelectColumns r a -> a #

toList :: SelectColumns r a -> [a] #

null :: SelectColumns r a -> Bool #

length :: SelectColumns r a -> Int #

elem :: Eq a => a -> SelectColumns r a -> Bool #

maximum :: Ord a => SelectColumns r a -> a #

minimum :: Ord a => SelectColumns r a -> a #

sum :: Num a => SelectColumns r a -> a #

product :: Num a => SelectColumns r a -> a #

ConstrainSASNames Traversable r => Traversable (SelectColumns r) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> SelectColumns r a -> f (SelectColumns r b) #

sequenceA :: Applicative f => SelectColumns r (f a) -> f (SelectColumns r a) #

mapM :: Monad m => (a -> m b) -> SelectColumns r a -> m (SelectColumns r b) #

sequence :: Monad m => SelectColumns r (m a) -> m (SelectColumns r a) #

ConstrainSNames Eq r a => Eq (SelectColumns r a) Source # 

Methods

(==) :: SelectColumns r a -> SelectColumns r a -> Bool #

(/=) :: SelectColumns r a -> SelectColumns r a -> Bool #

(ConstrainSNames Data r a, Data r) => Data (SelectColumns r a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SelectColumns r a -> c (SelectColumns r a) #

gunfold :: (forall b c. Data b => c (b -> c) -> c c) -> (forall b. b -> c b) -> Constr -> c (SelectColumns r a) #

toConstr :: SelectColumns r a -> Constr #

dataTypeOf :: SelectColumns r a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (SelectColumns r a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SelectColumns r a)) #

gmapT :: (forall b. Data b => b -> b) -> SelectColumns r a -> SelectColumns r a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SelectColumns r a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SelectColumns r a -> r #

gmapQ :: (forall d. Data d => d -> u) -> SelectColumns r a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SelectColumns r a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SelectColumns r a -> m (SelectColumns r a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SelectColumns r a -> m (SelectColumns r a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SelectColumns r a -> m (SelectColumns r a) #

ConstrainSNames Ord r a => Ord (SelectColumns r a) Source # 
ConstrainSNames Show r a => Show (SelectColumns r a) Source # 
Generic (SelectColumns r a) Source # 

Associated Types

type Rep (SelectColumns r a) :: * -> * #

Methods

from :: SelectColumns r a -> Rep (SelectColumns r a) x #

to :: Rep (SelectColumns r a) x -> SelectColumns r a #

ConstrainSNames ToJSON r a => ToJSON (SelectColumns r a) Source # 
ConstrainSNames FromJSON r a => FromJSON (SelectColumns r a) Source # 
HasTables (SelectColumns ResolvedNames a) Source # 
HasColumns (SelectColumns ResolvedNames a) Source # 

Methods

goColumns :: SelectColumns ResolvedNames a -> Observer Source #

HasInfo (SelectColumns r a) Source # 

Associated Types

type Info (SelectColumns r a) :: * Source #

type EvalResult e (SelectColumns ResolvedNames Range) Source # 
type Rep (SelectColumns r a) Source # 
type Rep (SelectColumns r a) = D1 * (MetaData "SelectColumns" "Database.Sql.Type.Query" "queryparser-0.1.0.1-L3r1ujeH5Ss7CLthXKM008" False) (C1 * (MetaCons "SelectColumns" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "selectColumnsInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Just Symbol "selectColumnsList") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Selection r a]))))
type Info (SelectColumns r a) Source # 
type Info (SelectColumns r a) = a

data SelectFrom r a Source #

Constructors

SelectFrom a [Tablish r a] 

Instances

Evaluation e => Evaluate e (SelectFrom ResolvedNames Range) Source # 
ConstrainSASNames Functor r => Functor (SelectFrom r) Source # 

Methods

fmap :: (a -> b) -> SelectFrom r a -> SelectFrom r b #

(<$) :: a -> SelectFrom r b -> SelectFrom r a #

ConstrainSASNames Foldable r => Foldable (SelectFrom r) Source # 

Methods

fold :: Monoid m => SelectFrom r m -> m #

foldMap :: Monoid m => (a -> m) -> SelectFrom r a -> m #

foldr :: (a -> b -> b) -> b -> SelectFrom r a -> b #

foldr' :: (a -> b -> b) -> b -> SelectFrom r a -> b #

foldl :: (b -> a -> b) -> b -> SelectFrom r a -> b #

foldl' :: (b -> a -> b) -> b -> SelectFrom r a -> b #

foldr1 :: (a -> a -> a) -> SelectFrom r a -> a #

foldl1 :: (a -> a -> a) -> SelectFrom r a -> a #

toList :: SelectFrom r a -> [a] #

null :: SelectFrom r a -> Bool #

length :: SelectFrom r a -> Int #

elem :: Eq a => a -> SelectFrom r a -> Bool #

maximum :: Ord a => SelectFrom r a -> a #

minimum :: Ord a => SelectFrom r a -> a #

sum :: Num a => SelectFrom r a -> a #

product :: Num a => SelectFrom r a -> a #

ConstrainSASNames Traversable r => Traversable (SelectFrom r) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> SelectFrom r a -> f (SelectFrom r b) #

sequenceA :: Applicative f => SelectFrom r (f a) -> f (SelectFrom r a) #

mapM :: Monad m => (a -> m b) -> SelectFrom r a -> m (SelectFrom r b) #

sequence :: Monad m => SelectFrom r (m a) -> m (SelectFrom r a) #

ConstrainSNames Eq r a => Eq (SelectFrom r a) Source # 

Methods

(==) :: SelectFrom r a -> SelectFrom r a -> Bool #

(/=) :: SelectFrom r a -> SelectFrom r a -> Bool #

(ConstrainSNames Data r a, Data r) => Data (SelectFrom r a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SelectFrom r a -> c (SelectFrom r a) #

gunfold :: (forall b c. Data b => c (b -> c) -> c c) -> (forall b. b -> c b) -> Constr -> c (SelectFrom r a) #

toConstr :: SelectFrom r a -> Constr #

dataTypeOf :: SelectFrom r a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (SelectFrom r a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SelectFrom r a)) #

gmapT :: (forall b. Data b => b -> b) -> SelectFrom r a -> SelectFrom r a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SelectFrom r a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SelectFrom r a -> r #

gmapQ :: (forall d. Data d => d -> u) -> SelectFrom r a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SelectFrom r a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SelectFrom r a -> m (SelectFrom r a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SelectFrom r a -> m (SelectFrom r a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SelectFrom r a -> m (SelectFrom r a) #

ConstrainSNames Ord r a => Ord (SelectFrom r a) Source # 

Methods

compare :: SelectFrom r a -> SelectFrom r a -> Ordering #

(<) :: SelectFrom r a -> SelectFrom r a -> Bool #

(<=) :: SelectFrom r a -> SelectFrom r a -> Bool #

(>) :: SelectFrom r a -> SelectFrom r a -> Bool #

(>=) :: SelectFrom r a -> SelectFrom r a -> Bool #

max :: SelectFrom r a -> SelectFrom r a -> SelectFrom r a #

min :: SelectFrom r a -> SelectFrom r a -> SelectFrom r a #

ConstrainSNames Show r a => Show (SelectFrom r a) Source # 

Methods

showsPrec :: Int -> SelectFrom r a -> ShowS #

show :: SelectFrom r a -> String #

showList :: [SelectFrom r a] -> ShowS #

Generic (SelectFrom r a) Source # 

Associated Types

type Rep (SelectFrom r a) :: * -> * #

Methods

from :: SelectFrom r a -> Rep (SelectFrom r a) x #

to :: Rep (SelectFrom r a) x -> SelectFrom r a #

ConstrainSNames ToJSON r a => ToJSON (SelectFrom r a) Source # 
ConstrainSNames FromJSON r a => FromJSON (SelectFrom r a) Source # 
HasTables (SelectFrom ResolvedNames a) Source # 
HasColumns (SelectFrom ResolvedNames a) Source # 

Methods

goColumns :: SelectFrom ResolvedNames a -> Observer Source #

HasInfo (SelectFrom r a) Source # 

Associated Types

type Info (SelectFrom r a) :: * Source #

Methods

getInfo :: SelectFrom r a -> Info (SelectFrom r a) Source #

type EvalResult e (SelectFrom ResolvedNames Range) Source # 
type Rep (SelectFrom r a) Source # 
type Rep (SelectFrom r a) = D1 * (MetaData "SelectFrom" "Database.Sql.Type.Query" "queryparser-0.1.0.1-L3r1ujeH5Ss7CLthXKM008" False) (C1 * (MetaCons "SelectFrom" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Tablish r a]))))
type Info (SelectFrom r a) Source # 
type Info (SelectFrom r a) = a

data TablishAliases a Source #

Instances

Functor TablishAliases Source # 

Methods

fmap :: (a -> b) -> TablishAliases a -> TablishAliases b #

(<$) :: a -> TablishAliases b -> TablishAliases a #

Foldable TablishAliases Source # 

Methods

fold :: Monoid m => TablishAliases m -> m #

foldMap :: Monoid m => (a -> m) -> TablishAliases a -> m #

foldr :: (a -> b -> b) -> b -> TablishAliases a -> b #

foldr' :: (a -> b -> b) -> b -> TablishAliases a -> b #

foldl :: (b -> a -> b) -> b -> TablishAliases a -> b #

foldl' :: (b -> a -> b) -> b -> TablishAliases a -> b #

foldr1 :: (a -> a -> a) -> TablishAliases a -> a #

foldl1 :: (a -> a -> a) -> TablishAliases a -> a #

toList :: TablishAliases a -> [a] #

null :: TablishAliases a -> Bool #

length :: TablishAliases a -> Int #

elem :: Eq a => a -> TablishAliases a -> Bool #

maximum :: Ord a => TablishAliases a -> a #

minimum :: Ord a => TablishAliases a -> a #

sum :: Num a => TablishAliases a -> a #

product :: Num a => TablishAliases a -> a #

Traversable TablishAliases Source # 

Methods

traverse :: Applicative f => (a -> f b) -> TablishAliases a -> f (TablishAliases b) #

sequenceA :: Applicative f => TablishAliases (f a) -> f (TablishAliases a) #

mapM :: Monad m => (a -> m b) -> TablishAliases a -> m (TablishAliases b) #

sequence :: Monad m => TablishAliases (m a) -> m (TablishAliases a) #

Eq a => Eq (TablishAliases a) Source # 
Data a => Data (TablishAliases a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TablishAliases a -> c (TablishAliases a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TablishAliases a) #

toConstr :: TablishAliases a -> Constr #

dataTypeOf :: TablishAliases a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (TablishAliases a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TablishAliases a)) #

gmapT :: (forall b. Data b => b -> b) -> TablishAliases a -> TablishAliases a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TablishAliases a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TablishAliases a -> r #

gmapQ :: (forall d. Data d => d -> u) -> TablishAliases a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TablishAliases a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TablishAliases a -> m (TablishAliases a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TablishAliases a -> m (TablishAliases a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TablishAliases a -> m (TablishAliases a) #

Ord a => Ord (TablishAliases a) Source # 
Show a => Show (TablishAliases a) Source # 
Generic (TablishAliases a) Source # 

Associated Types

type Rep (TablishAliases a) :: * -> * #

ToJSON a => ToJSON (TablishAliases a) Source # 
FromJSON a => FromJSON (TablishAliases a) Source # 
type Rep (TablishAliases a) Source # 
type Rep (TablishAliases a) = D1 * (MetaData "TablishAliases" "Database.Sql.Type.Query" "queryparser-0.1.0.1-L3r1ujeH5Ss7CLthXKM008" False) ((:+:) * (C1 * (MetaCons "TablishAliasesNone" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "TablishAliasesT" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (TableAlias a)))) (C1 * (MetaCons "TablishAliasesTC" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (TableAlias a))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ColumnAlias a]))))))

data Tablish r a Source #

Instances

Evaluation e => Evaluate e (Tablish ResolvedNames Range) Source # 
ConstrainSASNames Functor r => Functor (Tablish r) Source # 

Methods

fmap :: (a -> b) -> Tablish r a -> Tablish r b #

(<$) :: a -> Tablish r b -> Tablish r a #

ConstrainSASNames Foldable r => Foldable (Tablish r) Source # 

Methods

fold :: Monoid m => Tablish r m -> m #

foldMap :: Monoid m => (a -> m) -> Tablish r a -> m #

foldr :: (a -> b -> b) -> b -> Tablish r a -> b #

foldr' :: (a -> b -> b) -> b -> Tablish r a -> b #

foldl :: (b -> a -> b) -> b -> Tablish r a -> b #

foldl' :: (b -> a -> b) -> b -> Tablish r a -> b #

foldr1 :: (a -> a -> a) -> Tablish r a -> a #

foldl1 :: (a -> a -> a) -> Tablish r a -> a #

toList :: Tablish r a -> [a] #

null :: Tablish r a -> Bool #

length :: Tablish r a -> Int #

elem :: Eq a => a -> Tablish r a -> Bool #

maximum :: Ord a => Tablish r a -> a #

minimum :: Ord a => Tablish r a -> a #

sum :: Num a => Tablish r a -> a #

product :: Num a => Tablish r a -> a #

ConstrainSASNames Traversable r => Traversable (Tablish r) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Tablish r a -> f (Tablish r b) #

sequenceA :: Applicative f => Tablish r (f a) -> f (Tablish r a) #

mapM :: Monad m => (a -> m b) -> Tablish r a -> m (Tablish r b) #

sequence :: Monad m => Tablish r (m a) -> m (Tablish r a) #

ConstrainSNames Eq r a => Eq (Tablish r a) Source # 

Methods

(==) :: Tablish r a -> Tablish r a -> Bool #

(/=) :: Tablish r a -> Tablish r a -> Bool #

(ConstrainSNames Data r a, Data r) => Data (Tablish r a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Tablish r a -> c (Tablish r a) #

gunfold :: (forall b c. Data b => c (b -> c) -> c c) -> (forall b. b -> c b) -> Constr -> c (Tablish r a) #

toConstr :: Tablish r a -> Constr #

dataTypeOf :: Tablish r a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Tablish r a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Tablish r a)) #

gmapT :: (forall b. Data b => b -> b) -> Tablish r a -> Tablish r a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tablish r a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tablish r a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Tablish r a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Tablish r a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tablish r a -> m (Tablish r a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tablish r a -> m (Tablish r a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tablish r a -> m (Tablish r a) #

ConstrainSNames Ord r a => Ord (Tablish r a) Source # 

Methods

compare :: Tablish r a -> Tablish r a -> Ordering #

(<) :: Tablish r a -> Tablish r a -> Bool #

(<=) :: Tablish r a -> Tablish r a -> Bool #

(>) :: Tablish r a -> Tablish r a -> Bool #

(>=) :: Tablish r a -> Tablish r a -> Bool #

max :: Tablish r a -> Tablish r a -> Tablish r a #

min :: Tablish r a -> Tablish r a -> Tablish r a #

ConstrainSNames Show r a => Show (Tablish r a) Source # 

Methods

showsPrec :: Int -> Tablish r a -> ShowS #

show :: Tablish r a -> String #

showList :: [Tablish r a] -> ShowS #

Generic (Tablish r a) Source # 

Associated Types

type Rep (Tablish r a) :: * -> * #

Methods

from :: Tablish r a -> Rep (Tablish r a) x #

to :: Rep (Tablish r a) x -> Tablish r a #

ConstrainSNames ToJSON r a => ToJSON (Tablish r a) Source # 
ConstrainSNames FromJSON r a => FromJSON (Tablish r a) Source # 
HasTables (Tablish ResolvedNames a) Source # 
HasColumns (Tablish ResolvedNames a) Source # 

Methods

goColumns :: Tablish ResolvedNames a -> Observer Source #

HasInfo (Tablish r a) Source # 

Associated Types

type Info (Tablish r a) :: * Source #

Methods

getInfo :: Tablish r a -> Info (Tablish r a) Source #

type EvalResult e (Tablish ResolvedNames Range) Source # 
type Rep (Tablish r a) Source # 
type Rep (Tablish r a) = D1 * (MetaData "Tablish" "Database.Sql.Type.Query" "queryparser-0.1.0.1-L3r1ujeH5Ss7CLthXKM008" False) ((:+:) * ((:+:) * (C1 * (MetaCons "TablishTable" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (TablishAliases a))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (TableRef r a)))))) (C1 * (MetaCons "TablishSubQuery" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (TablishAliases a))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Query r a))))))) ((:+:) * (C1 * (MetaCons "TablishJoin" PrefixI False) ((:*:) * ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (JoinType a)))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (JoinCondition r a))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Tablish r a))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Tablish r a))))))) (C1 * (MetaCons "TablishLateralView" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (LateralView r a))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe (Tablish r a)))))))))
type Info (Tablish r a) Source # 
type Info (Tablish r a) = a

data JoinType a Source #

Constructors

JoinInner a 
JoinLeft a 
JoinRight a 
JoinFull a 
JoinSemi a 

Instances

Functor JoinType Source # 

Methods

fmap :: (a -> b) -> JoinType a -> JoinType b #

(<$) :: a -> JoinType b -> JoinType a #

Foldable JoinType Source # 

Methods

fold :: Monoid m => JoinType m -> m #

foldMap :: Monoid m => (a -> m) -> JoinType a -> m #

foldr :: (a -> b -> b) -> b -> JoinType a -> b #

foldr' :: (a -> b -> b) -> b -> JoinType a -> b #

foldl :: (b -> a -> b) -> b -> JoinType a -> b #

foldl' :: (b -> a -> b) -> b -> JoinType a -> b #

foldr1 :: (a -> a -> a) -> JoinType a -> a #

foldl1 :: (a -> a -> a) -> JoinType a -> a #

toList :: JoinType a -> [a] #

null :: JoinType a -> Bool #

length :: JoinType a -> Int #

elem :: Eq a => a -> JoinType a -> Bool #

maximum :: Ord a => JoinType a -> a #

minimum :: Ord a => JoinType a -> a #

sum :: Num a => JoinType a -> a #

product :: Num a => JoinType a -> a #

Traversable JoinType Source # 

Methods

traverse :: Applicative f => (a -> f b) -> JoinType a -> f (JoinType b) #

sequenceA :: Applicative f => JoinType (f a) -> f (JoinType a) #

mapM :: Monad m => (a -> m b) -> JoinType a -> m (JoinType b) #

sequence :: Monad m => JoinType (m a) -> m (JoinType a) #

Eq a => Eq (JoinType a) Source # 

Methods

(==) :: JoinType a -> JoinType a -> Bool #

(/=) :: JoinType a -> JoinType a -> Bool #

Data a => Data (JoinType a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JoinType a -> c (JoinType a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (JoinType a) #

toConstr :: JoinType a -> Constr #

dataTypeOf :: JoinType a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (JoinType a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (JoinType a)) #

gmapT :: (forall b. Data b => b -> b) -> JoinType a -> JoinType a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JoinType a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JoinType a -> r #

gmapQ :: (forall d. Data d => d -> u) -> JoinType a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> JoinType a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> JoinType a -> m (JoinType a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JoinType a -> m (JoinType a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JoinType a -> m (JoinType a) #

Ord a => Ord (JoinType a) Source # 

Methods

compare :: JoinType a -> JoinType a -> Ordering #

(<) :: JoinType a -> JoinType a -> Bool #

(<=) :: JoinType a -> JoinType a -> Bool #

(>) :: JoinType a -> JoinType a -> Bool #

(>=) :: JoinType a -> JoinType a -> Bool #

max :: JoinType a -> JoinType a -> JoinType a #

min :: JoinType a -> JoinType a -> JoinType a #

Show a => Show (JoinType a) Source # 

Methods

showsPrec :: Int -> JoinType a -> ShowS #

show :: JoinType a -> String #

showList :: [JoinType a] -> ShowS #

Generic (JoinType a) Source # 

Associated Types

type Rep (JoinType a) :: * -> * #

Methods

from :: JoinType a -> Rep (JoinType a) x #

to :: Rep (JoinType a) x -> JoinType a #

ToJSON a => ToJSON (JoinType a) Source # 
FromJSON a => FromJSON (JoinType a) Source # 
HasInfo (JoinType a) Source # 

Associated Types

type Info (JoinType a) :: * Source #

Methods

getInfo :: JoinType a -> Info (JoinType a) Source #

type Rep (JoinType a) Source # 
type Info (JoinType a) Source # 
type Info (JoinType a) = a

data JoinCondition r a Source #

Constructors

JoinNatural a (NaturalColumns r a) 
JoinOn (Expr r a) 
JoinUsing a [UsingColumn r a] 

Instances

Evaluation e => Evaluate e (JoinCondition ResolvedNames Range) Source # 
ConstrainSASNames Functor r => Functor (JoinCondition r) Source # 

Methods

fmap :: (a -> b) -> JoinCondition r a -> JoinCondition r b #

(<$) :: a -> JoinCondition r b -> JoinCondition r a #

ConstrainSASNames Foldable r => Foldable (JoinCondition r) Source # 

Methods

fold :: Monoid m => JoinCondition r m -> m #

foldMap :: Monoid m => (a -> m) -> JoinCondition r a -> m #

foldr :: (a -> b -> b) -> b -> JoinCondition r a -> b #

foldr' :: (a -> b -> b) -> b -> JoinCondition r a -> b #

foldl :: (b -> a -> b) -> b -> JoinCondition r a -> b #

foldl' :: (b -> a -> b) -> b -> JoinCondition r a -> b #

foldr1 :: (a -> a -> a) -> JoinCondition r a -> a #

foldl1 :: (a -> a -> a) -> JoinCondition r a -> a #

toList :: JoinCondition r a -> [a] #

null :: JoinCondition r a -> Bool #

length :: JoinCondition r a -> Int #

elem :: Eq a => a -> JoinCondition r a -> Bool #

maximum :: Ord a => JoinCondition r a -> a #

minimum :: Ord a => JoinCondition r a -> a #

sum :: Num a => JoinCondition r a -> a #

product :: Num a => JoinCondition r a -> a #

ConstrainSASNames Traversable r => Traversable (JoinCondition r) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> JoinCondition r a -> f (JoinCondition r b) #

sequenceA :: Applicative f => JoinCondition r (f a) -> f (JoinCondition r a) #

mapM :: Monad m => (a -> m b) -> JoinCondition r a -> m (JoinCondition r b) #

sequence :: Monad m => JoinCondition r (m a) -> m (JoinCondition r a) #

ConstrainSNames Eq r a => Eq (JoinCondition r a) Source # 

Methods

(==) :: JoinCondition r a -> JoinCondition r a -> Bool #

(/=) :: JoinCondition r a -> JoinCondition r a -> Bool #

(ConstrainSNames Data r a, Data r) => Data (JoinCondition r a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JoinCondition r a -> c (JoinCondition r a) #

gunfold :: (forall b c. Data b => c (b -> c) -> c c) -> (forall b. b -> c b) -> Constr -> c (JoinCondition r a) #

toConstr :: JoinCondition r a -> Constr #

dataTypeOf :: JoinCondition r a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (JoinCondition r a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (JoinCondition r a)) #

gmapT :: (forall b. Data b => b -> b) -> JoinCondition r a -> JoinCondition r a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JoinCondition r a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JoinCondition r a -> r #

gmapQ :: (forall d. Data d => d -> u) -> JoinCondition r a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> JoinCondition r a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> JoinCondition r a -> m (JoinCondition r a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JoinCondition r a -> m (JoinCondition r a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JoinCondition r a -> m (JoinCondition r a) #

ConstrainSNames Ord r a => Ord (JoinCondition r a) Source # 
ConstrainSNames Show r a => Show (JoinCondition r a) Source # 
Generic (JoinCondition r a) Source # 

Associated Types

type Rep (JoinCondition r a) :: * -> * #

Methods

from :: JoinCondition r a -> Rep (JoinCondition r a) x #

to :: Rep (JoinCondition r a) x -> JoinCondition r a #

ConstrainSNames ToJSON r a => ToJSON (JoinCondition r a) Source # 
ConstrainSNames FromJSON r a => FromJSON (JoinCondition r a) Source # 
HasColumns (JoinCondition ResolvedNames a) Source # 

Methods

goColumns :: JoinCondition ResolvedNames a -> Observer Source #

HasInfo (JoinCondition r a) Source # 

Associated Types

type Info (JoinCondition r a) :: * Source #

type EvalResult e (JoinCondition ResolvedNames Range) Source # 
type Rep (JoinCondition r a) Source # 
type Info (JoinCondition r a) Source # 
type Info (JoinCondition r a) = a

data LateralView r a Source #

Instances

ConstrainSASNames Functor r => Functor (LateralView r) Source # 

Methods

fmap :: (a -> b) -> LateralView r a -> LateralView r b #

(<$) :: a -> LateralView r b -> LateralView r a #

ConstrainSASNames Foldable r => Foldable (LateralView r) Source # 

Methods

fold :: Monoid m => LateralView r m -> m #

foldMap :: Monoid m => (a -> m) -> LateralView r a -> m #

foldr :: (a -> b -> b) -> b -> LateralView r a -> b #

foldr' :: (a -> b -> b) -> b -> LateralView r a -> b #

foldl :: (b -> a -> b) -> b -> LateralView r a -> b #

foldl' :: (b -> a -> b) -> b -> LateralView r a -> b #

foldr1 :: (a -> a -> a) -> LateralView r a -> a #

foldl1 :: (a -> a -> a) -> LateralView r a -> a #

toList :: LateralView r a -> [a] #

null :: LateralView r a -> Bool #

length :: LateralView r a -> Int #

elem :: Eq a => a -> LateralView r a -> Bool #

maximum :: Ord a => LateralView r a -> a #

minimum :: Ord a => LateralView r a -> a #

sum :: Num a => LateralView r a -> a #

product :: Num a => LateralView r a -> a #

ConstrainSASNames Traversable r => Traversable (LateralView r) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> LateralView r a -> f (LateralView r b) #

sequenceA :: Applicative f => LateralView r (f a) -> f (LateralView r a) #

mapM :: Monad m => (a -> m b) -> LateralView r a -> m (LateralView r b) #

sequence :: Monad m => LateralView r (m a) -> m (LateralView r a) #

ConstrainSNames Eq r a => Eq (LateralView r a) Source # 

Methods

(==) :: LateralView r a -> LateralView r a -> Bool #

(/=) :: LateralView r a -> LateralView r a -> Bool #

(ConstrainSNames Data r a, Data r) => Data (LateralView r a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LateralView r a -> c (LateralView r a) #

gunfold :: (forall b c. Data b => c (b -> c) -> c c) -> (forall b. b -> c b) -> Constr -> c (LateralView r a) #

toConstr :: LateralView r a -> Constr #

dataTypeOf :: LateralView r a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (LateralView r a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LateralView r a)) #

gmapT :: (forall b. Data b => b -> b) -> LateralView r a -> LateralView r a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LateralView r a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LateralView r a -> r #

gmapQ :: (forall d. Data d => d -> u) -> LateralView r a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LateralView r a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LateralView r a -> m (LateralView r a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LateralView r a -> m (LateralView r a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LateralView r a -> m (LateralView r a) #

ConstrainSNames Ord r a => Ord (LateralView r a) Source # 

Methods

compare :: LateralView r a -> LateralView r a -> Ordering #

(<) :: LateralView r a -> LateralView r a -> Bool #

(<=) :: LateralView r a -> LateralView r a -> Bool #

(>) :: LateralView r a -> LateralView r a -> Bool #

(>=) :: LateralView r a -> LateralView r a -> Bool #

max :: LateralView r a -> LateralView r a -> LateralView r a #

min :: LateralView r a -> LateralView r a -> LateralView r a #

ConstrainSNames Show r a => Show (LateralView r a) Source # 

Methods

showsPrec :: Int -> LateralView r a -> ShowS #

show :: LateralView r a -> String #

showList :: [LateralView r a] -> ShowS #

Generic (LateralView r a) Source # 

Associated Types

type Rep (LateralView r a) :: * -> * #

Methods

from :: LateralView r a -> Rep (LateralView r a) x #

to :: Rep (LateralView r a) x -> LateralView r a #

ConstrainSNames ToJSON r a => ToJSON (LateralView r a) Source # 
ConstrainSNames FromJSON r a => FromJSON (LateralView r a) Source # 
HasColumns (LateralView ResolvedNames a) Source # 

Methods

goColumns :: LateralView ResolvedNames a -> Observer Source #

type Rep (LateralView r a) Source # 
type Rep (LateralView r a) = D1 * (MetaData "LateralView" "Database.Sql.Type.Query" "queryparser-0.1.0.1-L3r1ujeH5Ss7CLthXKM008" False) (C1 * (MetaCons "LateralView" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "lateralViewInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Just Symbol "lateralViewOuter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe a)))) ((:*:) * (S1 * (MetaSel (Just Symbol "lateralViewExprs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Expr r a])) ((:*:) * (S1 * (MetaSel (Just Symbol "lateralViewWithOrdinality") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "lateralViewAliases") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (TablishAliases a)))))))

data SelectWhere r a Source #

Constructors

SelectWhere a (Expr r a) 

Instances

Evaluation e => Evaluate e (SelectWhere ResolvedNames Range) Source # 
ConstrainSASNames Functor r => Functor (SelectWhere r) Source # 

Methods

fmap :: (a -> b) -> SelectWhere r a -> SelectWhere r b #

(<$) :: a -> SelectWhere r b -> SelectWhere r a #

ConstrainSASNames Foldable r => Foldable (SelectWhere r) Source # 

Methods

fold :: Monoid m => SelectWhere r m -> m #

foldMap :: Monoid m => (a -> m) -> SelectWhere r a -> m #

foldr :: (a -> b -> b) -> b -> SelectWhere r a -> b #

foldr' :: (a -> b -> b) -> b -> SelectWhere r a -> b #

foldl :: (b -> a -> b) -> b -> SelectWhere r a -> b #

foldl' :: (b -> a -> b) -> b -> SelectWhere r a -> b #

foldr1 :: (a -> a -> a) -> SelectWhere r a -> a #

foldl1 :: (a -> a -> a) -> SelectWhere r a -> a #

toList :: SelectWhere r a -> [a] #

null :: SelectWhere r a -> Bool #

length :: SelectWhere r a -> Int #

elem :: Eq a => a -> SelectWhere r a -> Bool #

maximum :: Ord a => SelectWhere r a -> a #

minimum :: Ord a => SelectWhere r a -> a #

sum :: Num a => SelectWhere r a -> a #

product :: Num a => SelectWhere r a -> a #

ConstrainSASNames Traversable r => Traversable (SelectWhere r) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> SelectWhere r a -> f (SelectWhere r b) #

sequenceA :: Applicative f => SelectWhere r (f a) -> f (SelectWhere r a) #

mapM :: Monad m => (a -> m b) -> SelectWhere r a -> m (SelectWhere r b) #

sequence :: Monad m => SelectWhere r (m a) -> m (SelectWhere r a) #

ConstrainSNames Eq r a => Eq (SelectWhere r a) Source # 

Methods

(==) :: SelectWhere r a -> SelectWhere r a -> Bool #

(/=) :: SelectWhere r a -> SelectWhere r a -> Bool #

(ConstrainSNames Data r a, Data r) => Data (SelectWhere r a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SelectWhere r a -> c (SelectWhere r a) #

gunfold :: (forall b c. Data b => c (b -> c) -> c c) -> (forall b. b -> c b) -> Constr -> c (SelectWhere r a) #

toConstr :: SelectWhere r a -> Constr #

dataTypeOf :: SelectWhere r a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (SelectWhere r a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SelectWhere r a)) #

gmapT :: (forall b. Data b => b -> b) -> SelectWhere r a -> SelectWhere r a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SelectWhere r a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SelectWhere r a -> r #

gmapQ :: (forall d. Data d => d -> u) -> SelectWhere r a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SelectWhere r a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SelectWhere r a -> m (SelectWhere r a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SelectWhere r a -> m (SelectWhere r a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SelectWhere r a -> m (SelectWhere r a) #

ConstrainSNames Ord r a => Ord (SelectWhere r a) Source # 

Methods

compare :: SelectWhere r a -> SelectWhere r a -> Ordering #

(<) :: SelectWhere r a -> SelectWhere r a -> Bool #

(<=) :: SelectWhere r a -> SelectWhere r a -> Bool #

(>) :: SelectWhere r a -> SelectWhere r a -> Bool #

(>=) :: SelectWhere r a -> SelectWhere r a -> Bool #

max :: SelectWhere r a -> SelectWhere r a -> SelectWhere r a #

min :: SelectWhere r a -> SelectWhere r a -> SelectWhere r a #

ConstrainSNames Show r a => Show (SelectWhere r a) Source # 

Methods

showsPrec :: Int -> SelectWhere r a -> ShowS #

show :: SelectWhere r a -> String #

showList :: [SelectWhere r a] -> ShowS #

Generic (SelectWhere r a) Source # 

Associated Types

type Rep (SelectWhere r a) :: * -> * #

Methods

from :: SelectWhere r a -> Rep (SelectWhere r a) x #

to :: Rep (SelectWhere r a) x -> SelectWhere r a #

ConstrainSNames ToJSON r a => ToJSON (SelectWhere r a) Source # 
ConstrainSNames FromJSON r a => FromJSON (SelectWhere r a) Source # 
HasTables (SelectWhere ResolvedNames a) Source # 
HasColumns (SelectWhere ResolvedNames a) Source # 

Methods

goColumns :: SelectWhere ResolvedNames a -> Observer Source #

HasInfo (SelectWhere r a) Source # 

Associated Types

type Info (SelectWhere r a) :: * Source #

Methods

getInfo :: SelectWhere r a -> Info (SelectWhere r a) Source #

type EvalResult e (SelectWhere ResolvedNames Range) Source # 
type Rep (SelectWhere r a) Source # 
type Rep (SelectWhere r a) = D1 * (MetaData "SelectWhere" "Database.Sql.Type.Query" "queryparser-0.1.0.1-L3r1ujeH5Ss7CLthXKM008" False) (C1 * (MetaCons "SelectWhere" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Expr r a)))))
type Info (SelectWhere r a) Source # 
type Info (SelectWhere r a) = a

data SelectTimeseries r a Source #

Instances

Evaluation e => Evaluate e (SelectTimeseries ResolvedNames Range) Source # 
ConstrainSASNames Functor r => Functor (SelectTimeseries r) Source # 

Methods

fmap :: (a -> b) -> SelectTimeseries r a -> SelectTimeseries r b #

(<$) :: a -> SelectTimeseries r b -> SelectTimeseries r a #

ConstrainSASNames Foldable r => Foldable (SelectTimeseries r) Source # 

Methods

fold :: Monoid m => SelectTimeseries r m -> m #

foldMap :: Monoid m => (a -> m) -> SelectTimeseries r a -> m #

foldr :: (a -> b -> b) -> b -> SelectTimeseries r a -> b #

foldr' :: (a -> b -> b) -> b -> SelectTimeseries r a -> b #

foldl :: (b -> a -> b) -> b -> SelectTimeseries r a -> b #

foldl' :: (b -> a -> b) -> b -> SelectTimeseries r a -> b #

foldr1 :: (a -> a -> a) -> SelectTimeseries r a -> a #

foldl1 :: (a -> a -> a) -> SelectTimeseries r a -> a #

toList :: SelectTimeseries r a -> [a] #

null :: SelectTimeseries r a -> Bool #

length :: SelectTimeseries r a -> Int #

elem :: Eq a => a -> SelectTimeseries r a -> Bool #

maximum :: Ord a => SelectTimeseries r a -> a #

minimum :: Ord a => SelectTimeseries r a -> a #

sum :: Num a => SelectTimeseries r a -> a #

product :: Num a => SelectTimeseries r a -> a #

ConstrainSASNames Traversable r => Traversable (SelectTimeseries r) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> SelectTimeseries r a -> f (SelectTimeseries r b) #

sequenceA :: Applicative f => SelectTimeseries r (f a) -> f (SelectTimeseries r a) #

mapM :: Monad m => (a -> m b) -> SelectTimeseries r a -> m (SelectTimeseries r b) #

sequence :: Monad m => SelectTimeseries r (m a) -> m (SelectTimeseries r a) #

ConstrainSNames Eq r a => Eq (SelectTimeseries r a) Source # 
(ConstrainSNames Data r a, Data r) => Data (SelectTimeseries r a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SelectTimeseries r a -> c (SelectTimeseries r a) #

gunfold :: (forall b c. Data b => c (b -> c) -> c c) -> (forall b. b -> c b) -> Constr -> c (SelectTimeseries r a) #

toConstr :: SelectTimeseries r a -> Constr #

dataTypeOf :: SelectTimeseries r a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (SelectTimeseries r a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SelectTimeseries r a)) #

gmapT :: (forall b. Data b => b -> b) -> SelectTimeseries r a -> SelectTimeseries r a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SelectTimeseries r a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SelectTimeseries r a -> r #

gmapQ :: (forall d. Data d => d -> u) -> SelectTimeseries r a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SelectTimeseries r a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SelectTimeseries r a -> m (SelectTimeseries r a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SelectTimeseries r a -> m (SelectTimeseries r a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SelectTimeseries r a -> m (SelectTimeseries r a) #

ConstrainSNames Ord r a => Ord (SelectTimeseries r a) Source # 
ConstrainSNames Show r a => Show (SelectTimeseries r a) Source # 
Generic (SelectTimeseries r a) Source # 

Associated Types

type Rep (SelectTimeseries r a) :: * -> * #

ConstrainSNames ToJSON r a => ToJSON (SelectTimeseries r a) Source # 
ConstrainSNames FromJSON r a => FromJSON (SelectTimeseries r a) Source # 
HasTables (SelectTimeseries ResolvedNames a) Source # 
HasColumns (SelectTimeseries ResolvedNames a) Source # 
HasInfo (SelectTimeseries r a) Source # 

Associated Types

type Info (SelectTimeseries r a) :: * Source #

type EvalResult e (SelectTimeseries ResolvedNames Range) Source # 
type Rep (SelectTimeseries r a) Source # 
type Rep (SelectTimeseries r a) = D1 * (MetaData "SelectTimeseries" "Database.Sql.Type.Query" "queryparser-0.1.0.1-L3r1ujeH5Ss7CLthXKM008" False) (C1 * (MetaCons "SelectTimeseries" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "selectTimeseriesInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Just Symbol "selectTimeseriesSliceName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (ColumnAlias a)))) ((:*:) * (S1 * (MetaSel (Just Symbol "selectTimeseriesInterval") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Constant a))) ((:*:) * (S1 * (MetaSel (Just Symbol "selectTimeseriesPartition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe (Partition r a)))) (S1 * (MetaSel (Just Symbol "selectTimeseriesOrder") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Expr r a)))))))
type Info (SelectTimeseries r a) Source # 
type Info (SelectTimeseries r a) = a

data PositionOrExpr r a Source #

Instances

ConstrainSASNames Functor r => Functor (PositionOrExpr r) Source # 

Methods

fmap :: (a -> b) -> PositionOrExpr r a -> PositionOrExpr r b #

(<$) :: a -> PositionOrExpr r b -> PositionOrExpr r a #

ConstrainSASNames Foldable r => Foldable (PositionOrExpr r) Source # 

Methods

fold :: Monoid m => PositionOrExpr r m -> m #

foldMap :: Monoid m => (a -> m) -> PositionOrExpr r a -> m #

foldr :: (a -> b -> b) -> b -> PositionOrExpr r a -> b #

foldr' :: (a -> b -> b) -> b -> PositionOrExpr r a -> b #

foldl :: (b -> a -> b) -> b -> PositionOrExpr r a -> b #

foldl' :: (b -> a -> b) -> b -> PositionOrExpr r a -> b #

foldr1 :: (a -> a -> a) -> PositionOrExpr r a -> a #

foldl1 :: (a -> a -> a) -> PositionOrExpr r a -> a #

toList :: PositionOrExpr r a -> [a] #

null :: PositionOrExpr r a -> Bool #

length :: PositionOrExpr r a -> Int #

elem :: Eq a => a -> PositionOrExpr r a -> Bool #

maximum :: Ord a => PositionOrExpr r a -> a #

minimum :: Ord a => PositionOrExpr r a -> a #

sum :: Num a => PositionOrExpr r a -> a #

product :: Num a => PositionOrExpr r a -> a #

ConstrainSASNames Traversable r => Traversable (PositionOrExpr r) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> PositionOrExpr r a -> f (PositionOrExpr r b) #

sequenceA :: Applicative f => PositionOrExpr r (f a) -> f (PositionOrExpr r a) #

mapM :: Monad m => (a -> m b) -> PositionOrExpr r a -> m (PositionOrExpr r b) #

sequence :: Monad m => PositionOrExpr r (m a) -> m (PositionOrExpr r a) #

ConstrainSNames Eq r a => Eq (PositionOrExpr r a) Source # 
(ConstrainSNames Data r a, Data r) => Data (PositionOrExpr r a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PositionOrExpr r a -> c (PositionOrExpr r a) #

gunfold :: (forall b c. Data b => c (b -> c) -> c c) -> (forall b. b -> c b) -> Constr -> c (PositionOrExpr r a) #

toConstr :: PositionOrExpr r a -> Constr #

dataTypeOf :: PositionOrExpr r a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (PositionOrExpr r a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PositionOrExpr r a)) #

gmapT :: (forall b. Data b => b -> b) -> PositionOrExpr r a -> PositionOrExpr r a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PositionOrExpr r a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PositionOrExpr r a -> r #

gmapQ :: (forall d. Data d => d -> u) -> PositionOrExpr r a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PositionOrExpr r a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PositionOrExpr r a -> m (PositionOrExpr r a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PositionOrExpr r a -> m (PositionOrExpr r a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PositionOrExpr r a -> m (PositionOrExpr r a) #

ConstrainSNames Ord r a => Ord (PositionOrExpr r a) Source # 
ConstrainSNames Show r a => Show (PositionOrExpr r a) Source # 
Generic (PositionOrExpr r a) Source # 

Associated Types

type Rep (PositionOrExpr r a) :: * -> * #

Methods

from :: PositionOrExpr r a -> Rep (PositionOrExpr r a) x #

to :: Rep (PositionOrExpr r a) x -> PositionOrExpr r a #

(Arbitrary (PositionExpr r a), Arbitrary a) => Arbitrary (PositionOrExpr r a) Source # 
ConstrainSNames ToJSON r a => ToJSON (PositionOrExpr r a) Source # 
ConstrainSNames FromJSON r a => FromJSON (PositionOrExpr r a) Source # 
HasTables (PositionOrExpr ResolvedNames a) Source # 
HasInfo (PositionOrExpr r a) Source # 

Associated Types

type Info (PositionOrExpr r a) :: * Source #

type Rep (PositionOrExpr r a) Source # 
type Info (PositionOrExpr r a) Source # 
type Info (PositionOrExpr r a) = a

data GroupingElement r a Source #

Instances

ConstrainSASNames Functor r => Functor (GroupingElement r) Source # 

Methods

fmap :: (a -> b) -> GroupingElement r a -> GroupingElement r b #

(<$) :: a -> GroupingElement r b -> GroupingElement r a #

ConstrainSASNames Foldable r => Foldable (GroupingElement r) Source # 

Methods

fold :: Monoid m => GroupingElement r m -> m #

foldMap :: Monoid m => (a -> m) -> GroupingElement r a -> m #

foldr :: (a -> b -> b) -> b -> GroupingElement r a -> b #

foldr' :: (a -> b -> b) -> b -> GroupingElement r a -> b #

foldl :: (b -> a -> b) -> b -> GroupingElement r a -> b #

foldl' :: (b -> a -> b) -> b -> GroupingElement r a -> b #

foldr1 :: (a -> a -> a) -> GroupingElement r a -> a #

foldl1 :: (a -> a -> a) -> GroupingElement r a -> a #

toList :: GroupingElement r a -> [a] #

null :: GroupingElement r a -> Bool #

length :: GroupingElement r a -> Int #

elem :: Eq a => a -> GroupingElement r a -> Bool #

maximum :: Ord a => GroupingElement r a -> a #

minimum :: Ord a => GroupingElement r a -> a #

sum :: Num a => GroupingElement r a -> a #

product :: Num a => GroupingElement r a -> a #

ConstrainSASNames Traversable r => Traversable (GroupingElement r) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> GroupingElement r a -> f (GroupingElement r b) #

sequenceA :: Applicative f => GroupingElement r (f a) -> f (GroupingElement r a) #

mapM :: Monad m => (a -> m b) -> GroupingElement r a -> m (GroupingElement r b) #

sequence :: Monad m => GroupingElement r (m a) -> m (GroupingElement r a) #

ConstrainSNames Eq r a => Eq (GroupingElement r a) Source # 
(ConstrainSNames Data r a, Data r) => Data (GroupingElement r a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GroupingElement r a -> c (GroupingElement r a) #

gunfold :: (forall b c. Data b => c (b -> c) -> c c) -> (forall b. b -> c b) -> Constr -> c (GroupingElement r a) #

toConstr :: GroupingElement r a -> Constr #

dataTypeOf :: GroupingElement r a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (GroupingElement r a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GroupingElement r a)) #

gmapT :: (forall b. Data b => b -> b) -> GroupingElement r a -> GroupingElement r a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GroupingElement r a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GroupingElement r a -> r #

gmapQ :: (forall d. Data d => d -> u) -> GroupingElement r a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GroupingElement r a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GroupingElement r a -> m (GroupingElement r a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GroupingElement r a -> m (GroupingElement r a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GroupingElement r a -> m (GroupingElement r a) #

ConstrainSNames Ord r a => Ord (GroupingElement r a) Source # 
ConstrainSNames Show r a => Show (GroupingElement r a) Source # 
Generic (GroupingElement r a) Source # 

Associated Types

type Rep (GroupingElement r a) :: * -> * #

Methods

from :: GroupingElement r a -> Rep (GroupingElement r a) x #

to :: Rep (GroupingElement r a) x -> GroupingElement r a #

ConstrainSNames ToJSON r a => ToJSON (GroupingElement r a) Source # 
ConstrainSNames FromJSON r a => FromJSON (GroupingElement r a) Source # 
HasTables (GroupingElement ResolvedNames a) Source # 
HasInfo (GroupingElement r a) Source # 

Associated Types

type Info (GroupingElement r a) :: * Source #

type Rep (GroupingElement r a) Source # 
type Info (GroupingElement r a) Source # 
type Info (GroupingElement r a) = a

data SelectGroup r a Source #

Instances

Evaluation e => Evaluate e (SelectGroup ResolvedNames Range) Source # 
ConstrainSASNames Functor r => Functor (SelectGroup r) Source # 

Methods

fmap :: (a -> b) -> SelectGroup r a -> SelectGroup r b #

(<$) :: a -> SelectGroup r b -> SelectGroup r a #

ConstrainSASNames Foldable r => Foldable (SelectGroup r) Source # 

Methods

fold :: Monoid m => SelectGroup r m -> m #

foldMap :: Monoid m => (a -> m) -> SelectGroup r a -> m #

foldr :: (a -> b -> b) -> b -> SelectGroup r a -> b #

foldr' :: (a -> b -> b) -> b -> SelectGroup r a -> b #

foldl :: (b -> a -> b) -> b -> SelectGroup r a -> b #

foldl' :: (b -> a -> b) -> b -> SelectGroup r a -> b #

foldr1 :: (a -> a -> a) -> SelectGroup r a -> a #

foldl1 :: (a -> a -> a) -> SelectGroup r a -> a #

toList :: SelectGroup r a -> [a] #

null :: SelectGroup r a -> Bool #

length :: SelectGroup r a -> Int #

elem :: Eq a => a -> SelectGroup r a -> Bool #

maximum :: Ord a => SelectGroup r a -> a #

minimum :: Ord a => SelectGroup r a -> a #

sum :: Num a => SelectGroup r a -> a #

product :: Num a => SelectGroup r a -> a #

ConstrainSASNames Traversable r => Traversable (SelectGroup r) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> SelectGroup r a -> f (SelectGroup r b) #

sequenceA :: Applicative f => SelectGroup r (f a) -> f (SelectGroup r a) #

mapM :: Monad m => (a -> m b) -> SelectGroup r a -> m (SelectGroup r b) #

sequence :: Monad m => SelectGroup r (m a) -> m (SelectGroup r a) #

ConstrainSNames Eq r a => Eq (SelectGroup r a) Source # 

Methods

(==) :: SelectGroup r a -> SelectGroup r a -> Bool #

(/=) :: SelectGroup r a -> SelectGroup r a -> Bool #

(ConstrainSNames Data r a, Data r) => Data (SelectGroup r a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SelectGroup r a -> c (SelectGroup r a) #

gunfold :: (forall b c. Data b => c (b -> c) -> c c) -> (forall b. b -> c b) -> Constr -> c (SelectGroup r a) #

toConstr :: SelectGroup r a -> Constr #

dataTypeOf :: SelectGroup r a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (SelectGroup r a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SelectGroup r a)) #

gmapT :: (forall b. Data b => b -> b) -> SelectGroup r a -> SelectGroup r a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SelectGroup r a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SelectGroup r a -> r #

gmapQ :: (forall d. Data d => d -> u) -> SelectGroup r a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SelectGroup r a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SelectGroup r a -> m (SelectGroup r a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SelectGroup r a -> m (SelectGroup r a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SelectGroup r a -> m (SelectGroup r a) #

ConstrainSNames Ord r a => Ord (SelectGroup r a) Source # 

Methods

compare :: SelectGroup r a -> SelectGroup r a -> Ordering #

(<) :: SelectGroup r a -> SelectGroup r a -> Bool #

(<=) :: SelectGroup r a -> SelectGroup r a -> Bool #

(>) :: SelectGroup r a -> SelectGroup r a -> Bool #

(>=) :: SelectGroup r a -> SelectGroup r a -> Bool #

max :: SelectGroup r a -> SelectGroup r a -> SelectGroup r a #

min :: SelectGroup r a -> SelectGroup r a -> SelectGroup r a #

ConstrainSNames Show r a => Show (SelectGroup r a) Source # 

Methods

showsPrec :: Int -> SelectGroup r a -> ShowS #

show :: SelectGroup r a -> String #

showList :: [SelectGroup r a] -> ShowS #

Generic (SelectGroup r a) Source # 

Associated Types

type Rep (SelectGroup r a) :: * -> * #

Methods

from :: SelectGroup r a -> Rep (SelectGroup r a) x #

to :: Rep (SelectGroup r a) x -> SelectGroup r a #

ConstrainSNames ToJSON r a => ToJSON (SelectGroup r a) Source # 
ConstrainSNames FromJSON r a => FromJSON (SelectGroup r a) Source # 
HasTables (SelectGroup ResolvedNames a) Source # 
HasInfo (SelectGroup r a) Source # 

Associated Types

type Info (SelectGroup r a) :: * Source #

Methods

getInfo :: SelectGroup r a -> Info (SelectGroup r a) Source #

type EvalResult e (SelectGroup ResolvedNames Range) Source # 
type Rep (SelectGroup r a) Source # 
type Rep (SelectGroup r a) = D1 * (MetaData "SelectGroup" "Database.Sql.Type.Query" "queryparser-0.1.0.1-L3r1ujeH5Ss7CLthXKM008" False) (C1 * (MetaCons "SelectGroup" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "selectGroupInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Just Symbol "selectGroupGroupingElements") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [GroupingElement r a]))))
type Info (SelectGroup r a) Source # 
type Info (SelectGroup r a) = a

data SelectHaving r a Source #

Constructors

SelectHaving a [Expr r a] 

Instances

Evaluation e => Evaluate e (SelectHaving ResolvedNames Range) Source # 
ConstrainSASNames Functor r => Functor (SelectHaving r) Source # 

Methods

fmap :: (a -> b) -> SelectHaving r a -> SelectHaving r b #

(<$) :: a -> SelectHaving r b -> SelectHaving r a #

ConstrainSASNames Foldable r => Foldable (SelectHaving r) Source # 

Methods

fold :: Monoid m => SelectHaving r m -> m #

foldMap :: Monoid m => (a -> m) -> SelectHaving r a -> m #

foldr :: (a -> b -> b) -> b -> SelectHaving r a -> b #

foldr' :: (a -> b -> b) -> b -> SelectHaving r a -> b #

foldl :: (b -> a -> b) -> b -> SelectHaving r a -> b #

foldl' :: (b -> a -> b) -> b -> SelectHaving r a -> b #

foldr1 :: (a -> a -> a) -> SelectHaving r a -> a #

foldl1 :: (a -> a -> a) -> SelectHaving r a -> a #

toList :: SelectHaving r a -> [a] #

null :: SelectHaving r a -> Bool #

length :: SelectHaving r a -> Int #

elem :: Eq a => a -> SelectHaving r a -> Bool #

maximum :: Ord a => SelectHaving r a -> a #

minimum :: Ord a => SelectHaving r a -> a #

sum :: Num a => SelectHaving r a -> a #

product :: Num a => SelectHaving r a -> a #

ConstrainSASNames Traversable r => Traversable (SelectHaving r) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> SelectHaving r a -> f (SelectHaving r b) #

sequenceA :: Applicative f => SelectHaving r (f a) -> f (SelectHaving r a) #

mapM :: Monad m => (a -> m b) -> SelectHaving r a -> m (SelectHaving r b) #

sequence :: Monad m => SelectHaving r (m a) -> m (SelectHaving r a) #

ConstrainSNames Eq r a => Eq (SelectHaving r a) Source # 

Methods

(==) :: SelectHaving r a -> SelectHaving r a -> Bool #

(/=) :: SelectHaving r a -> SelectHaving r a -> Bool #

(ConstrainSNames Data r a, Data r) => Data (SelectHaving r a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SelectHaving r a -> c (SelectHaving r a) #

gunfold :: (forall b c. Data b => c (b -> c) -> c c) -> (forall b. b -> c b) -> Constr -> c (SelectHaving r a) #

toConstr :: SelectHaving r a -> Constr #

dataTypeOf :: SelectHaving r a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (SelectHaving r a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SelectHaving r a)) #

gmapT :: (forall b. Data b => b -> b) -> SelectHaving r a -> SelectHaving r a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SelectHaving r a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SelectHaving r a -> r #

gmapQ :: (forall d. Data d => d -> u) -> SelectHaving r a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SelectHaving r a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SelectHaving r a -> m (SelectHaving r a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SelectHaving r a -> m (SelectHaving r a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SelectHaving r a -> m (SelectHaving r a) #

ConstrainSNames Ord r a => Ord (SelectHaving r a) Source # 
ConstrainSNames Show r a => Show (SelectHaving r a) Source # 
Generic (SelectHaving r a) Source # 

Associated Types

type Rep (SelectHaving r a) :: * -> * #

Methods

from :: SelectHaving r a -> Rep (SelectHaving r a) x #

to :: Rep (SelectHaving r a) x -> SelectHaving r a #

ConstrainSNames ToJSON r a => ToJSON (SelectHaving r a) Source # 
ConstrainSNames FromJSON r a => FromJSON (SelectHaving r a) Source # 
HasTables (SelectHaving ResolvedNames a) Source # 
HasColumns (SelectHaving ResolvedNames a) Source # 

Methods

goColumns :: SelectHaving ResolvedNames a -> Observer Source #

HasInfo (SelectHaving r a) Source # 

Associated Types

type Info (SelectHaving r a) :: * Source #

Methods

getInfo :: SelectHaving r a -> Info (SelectHaving r a) Source #

type EvalResult e (SelectHaving ResolvedNames Range) Source # 
type Rep (SelectHaving r a) Source # 
type Rep (SelectHaving r a) = D1 * (MetaData "SelectHaving" "Database.Sql.Type.Query" "queryparser-0.1.0.1-L3r1ujeH5Ss7CLthXKM008" False) (C1 * (MetaCons "SelectHaving" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Expr r a]))))
type Info (SelectHaving r a) Source # 
type Info (SelectHaving r a) = a

data SelectNamedWindow r a Source #

Constructors

SelectNamedWindow a [NamedWindowExpr r a] 

Instances

ConstrainSASNames Functor r => Functor (SelectNamedWindow r) Source # 

Methods

fmap :: (a -> b) -> SelectNamedWindow r a -> SelectNamedWindow r b #

(<$) :: a -> SelectNamedWindow r b -> SelectNamedWindow r a #

ConstrainSASNames Foldable r => Foldable (SelectNamedWindow r) Source # 

Methods

fold :: Monoid m => SelectNamedWindow r m -> m #

foldMap :: Monoid m => (a -> m) -> SelectNamedWindow r a -> m #

foldr :: (a -> b -> b) -> b -> SelectNamedWindow r a -> b #

foldr' :: (a -> b -> b) -> b -> SelectNamedWindow r a -> b #

foldl :: (b -> a -> b) -> b -> SelectNamedWindow r a -> b #

foldl' :: (b -> a -> b) -> b -> SelectNamedWindow r a -> b #

foldr1 :: (a -> a -> a) -> SelectNamedWindow r a -> a #

foldl1 :: (a -> a -> a) -> SelectNamedWindow r a -> a #

toList :: SelectNamedWindow r a -> [a] #

null :: SelectNamedWindow r a -> Bool #

length :: SelectNamedWindow r a -> Int #

elem :: Eq a => a -> SelectNamedWindow r a -> Bool #

maximum :: Ord a => SelectNamedWindow r a -> a #

minimum :: Ord a => SelectNamedWindow r a -> a #

sum :: Num a => SelectNamedWindow r a -> a #

product :: Num a => SelectNamedWindow r a -> a #

ConstrainSASNames Traversable r => Traversable (SelectNamedWindow r) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> SelectNamedWindow r a -> f (SelectNamedWindow r b) #

sequenceA :: Applicative f => SelectNamedWindow r (f a) -> f (SelectNamedWindow r a) #

mapM :: Monad m => (a -> m b) -> SelectNamedWindow r a -> m (SelectNamedWindow r b) #

sequence :: Monad m => SelectNamedWindow r (m a) -> m (SelectNamedWindow r a) #

ConstrainSNames Eq r a => Eq (SelectNamedWindow r a) Source # 
(ConstrainSNames Data r a, Data r) => Data (SelectNamedWindow r a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SelectNamedWindow r a -> c (SelectNamedWindow r a) #

gunfold :: (forall b c. Data b => c (b -> c) -> c c) -> (forall b. b -> c b) -> Constr -> c (SelectNamedWindow r a) #

toConstr :: SelectNamedWindow r a -> Constr #

dataTypeOf :: SelectNamedWindow r a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (SelectNamedWindow r a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SelectNamedWindow r a)) #

gmapT :: (forall b. Data b => b -> b) -> SelectNamedWindow r a -> SelectNamedWindow r a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SelectNamedWindow r a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SelectNamedWindow r a -> r #

gmapQ :: (forall d. Data d => d -> u) -> SelectNamedWindow r a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SelectNamedWindow r a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SelectNamedWindow r a -> m (SelectNamedWindow r a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SelectNamedWindow r a -> m (SelectNamedWindow r a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SelectNamedWindow r a -> m (SelectNamedWindow r a) #

ConstrainSNames Ord r a => Ord (SelectNamedWindow r a) Source # 
ConstrainSNames Show r a => Show (SelectNamedWindow r a) Source # 
Generic (SelectNamedWindow r a) Source # 

Associated Types

type Rep (SelectNamedWindow r a) :: * -> * #

ConstrainSNames ToJSON r a => ToJSON (SelectNamedWindow r a) Source # 
ConstrainSNames FromJSON r a => FromJSON (SelectNamedWindow r a) Source # 
HasTables (SelectNamedWindow ResolvedNames a) Source # 
HasColumns (SelectNamedWindow ResolvedNames a) Source # 
HasInfo (SelectNamedWindow r a) Source # 

Associated Types

type Info (SelectNamedWindow r a) :: * Source #

type Rep (SelectNamedWindow r a) Source # 
type Rep (SelectNamedWindow r a) = D1 * (MetaData "SelectNamedWindow" "Database.Sql.Type.Query" "queryparser-0.1.0.1-L3r1ujeH5Ss7CLthXKM008" False) (C1 * (MetaCons "SelectNamedWindow" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [NamedWindowExpr r a]))))
type Info (SelectNamedWindow r a) Source # 
type Info (SelectNamedWindow r a) = a

data Order r a Source #

Constructors

Order a (PositionOrExpr r a) (OrderDirection (Maybe a)) (NullPosition (Maybe a)) 

Instances

ConstrainSASNames Functor r => Functor (Order r) Source # 

Methods

fmap :: (a -> b) -> Order r a -> Order r b #

(<$) :: a -> Order r b -> Order r a #

ConstrainSASNames Foldable r => Foldable (Order r) Source # 

Methods

fold :: Monoid m => Order r m -> m #

foldMap :: Monoid m => (a -> m) -> Order r a -> m #

foldr :: (a -> b -> b) -> b -> Order r a -> b #

foldr' :: (a -> b -> b) -> b -> Order r a -> b #

foldl :: (b -> a -> b) -> b -> Order r a -> b #

foldl' :: (b -> a -> b) -> b -> Order r a -> b #

foldr1 :: (a -> a -> a) -> Order r a -> a #

foldl1 :: (a -> a -> a) -> Order r a -> a #

toList :: Order r a -> [a] #

null :: Order r a -> Bool #

length :: Order r a -> Int #

elem :: Eq a => a -> Order r a -> Bool #

maximum :: Ord a => Order r a -> a #

minimum :: Ord a => Order r a -> a #

sum :: Num a => Order r a -> a #

product :: Num a => Order r a -> a #

ConstrainSASNames Traversable r => Traversable (Order r) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Order r a -> f (Order r b) #

sequenceA :: Applicative f => Order r (f a) -> f (Order r a) #

mapM :: Monad m => (a -> m b) -> Order r a -> m (Order r b) #

sequence :: Monad m => Order r (m a) -> m (Order r a) #

ConstrainSNames Eq r a => Eq (Order r a) Source # 

Methods

(==) :: Order r a -> Order r a -> Bool #

(/=) :: Order r a -> Order r a -> Bool #

(ConstrainSNames Data r a, Data r) => Data (Order r a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Order r a -> c (Order r a) #

gunfold :: (forall b c. Data b => c (b -> c) -> c c) -> (forall b. b -> c b) -> Constr -> c (Order r a) #

toConstr :: Order r a -> Constr #

dataTypeOf :: Order r a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Order r a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Order r a)) #

gmapT :: (forall b. Data b => b -> b) -> Order r a -> Order r a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Order r a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Order r a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Order r a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Order r a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Order r a -> m (Order r a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Order r a -> m (Order r a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Order r a -> m (Order r a) #

ConstrainSNames Ord r a => Ord (Order r a) Source # 

Methods

compare :: Order r a -> Order r a -> Ordering #

(<) :: Order r a -> Order r a -> Bool #

(<=) :: Order r a -> Order r a -> Bool #

(>) :: Order r a -> Order r a -> Bool #

(>=) :: Order r a -> Order r a -> Bool #

max :: Order r a -> Order r a -> Order r a #

min :: Order r a -> Order r a -> Order r a #

ConstrainSNames Show r a => Show (Order r a) Source # 

Methods

showsPrec :: Int -> Order r a -> ShowS #

show :: Order r a -> String #

showList :: [Order r a] -> ShowS #

Generic (Order r a) Source # 

Associated Types

type Rep (Order r a) :: * -> * #

Methods

from :: Order r a -> Rep (Order r a) x #

to :: Rep (Order r a) x -> Order r a #

(Arbitrary (PositionExpr r a), Arbitrary a) => Arbitrary (Order r a) Source # 

Methods

arbitrary :: Gen (Order r a) #

shrink :: Order r a -> [Order r a] #

ConstrainSNames ToJSON r a => ToJSON (Order r a) Source # 

Methods

toJSON :: Order r a -> Value #

toEncoding :: Order r a -> Encoding #

toJSONList :: [Order r a] -> Value #

toEncodingList :: [Order r a] -> Encoding #

ConstrainSNames FromJSON r a => FromJSON (Order r a) Source # 

Methods

parseJSON :: Value -> Parser (Order r a) #

parseJSONList :: Value -> Parser [Order r a] #

HasTables (Order ResolvedNames a) Source # 
HasInfo (Order r a) Source # 

Associated Types

type Info (Order r a) :: * Source #

Methods

getInfo :: Order r a -> Info (Order r a) Source #

type Rep (Order r a) Source # 
type Info (Order r a) Source # 
type Info (Order r a) = a

data OrderDirection a Source #

Constructors

OrderAsc a 
OrderDesc a 

Instances

Functor OrderDirection Source # 

Methods

fmap :: (a -> b) -> OrderDirection a -> OrderDirection b #

(<$) :: a -> OrderDirection b -> OrderDirection a #

Foldable OrderDirection Source # 

Methods

fold :: Monoid m => OrderDirection m -> m #

foldMap :: Monoid m => (a -> m) -> OrderDirection a -> m #

foldr :: (a -> b -> b) -> b -> OrderDirection a -> b #

foldr' :: (a -> b -> b) -> b -> OrderDirection a -> b #

foldl :: (b -> a -> b) -> b -> OrderDirection a -> b #

foldl' :: (b -> a -> b) -> b -> OrderDirection a -> b #

foldr1 :: (a -> a -> a) -> OrderDirection a -> a #

foldl1 :: (a -> a -> a) -> OrderDirection a -> a #

toList :: OrderDirection a -> [a] #

null :: OrderDirection a -> Bool #

length :: OrderDirection a -> Int #

elem :: Eq a => a -> OrderDirection a -> Bool #

maximum :: Ord a => OrderDirection a -> a #

minimum :: Ord a => OrderDirection a -> a #

sum :: Num a => OrderDirection a -> a #

product :: Num a => OrderDirection a -> a #

Traversable OrderDirection Source # 

Methods

traverse :: Applicative f => (a -> f b) -> OrderDirection a -> f (OrderDirection b) #

sequenceA :: Applicative f => OrderDirection (f a) -> f (OrderDirection a) #

mapM :: Monad m => (a -> m b) -> OrderDirection a -> m (OrderDirection b) #

sequence :: Monad m => OrderDirection (m a) -> m (OrderDirection a) #

Eq a => Eq (OrderDirection a) Source # 
Data a => Data (OrderDirection a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OrderDirection a -> c (OrderDirection a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (OrderDirection a) #

toConstr :: OrderDirection a -> Constr #

dataTypeOf :: OrderDirection a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (OrderDirection a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (OrderDirection a)) #

gmapT :: (forall b. Data b => b -> b) -> OrderDirection a -> OrderDirection a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OrderDirection a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OrderDirection a -> r #

gmapQ :: (forall d. Data d => d -> u) -> OrderDirection a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OrderDirection a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OrderDirection a -> m (OrderDirection a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderDirection a -> m (OrderDirection a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderDirection a -> m (OrderDirection a) #

Ord a => Ord (OrderDirection a) Source # 
Show a => Show (OrderDirection a) Source # 
Generic (OrderDirection a) Source # 

Associated Types

type Rep (OrderDirection a) :: * -> * #

Arbitrary a => Arbitrary (OrderDirection a) Source # 
ToJSON a => ToJSON (OrderDirection a) Source # 
FromJSON a => FromJSON (OrderDirection a) Source # 
HasInfo (OrderDirection a) Source # 

Associated Types

type Info (OrderDirection a) :: * Source #

type Rep (OrderDirection a) Source # 
type Rep (OrderDirection a) = D1 * (MetaData "OrderDirection" "Database.Sql.Type.Query" "queryparser-0.1.0.1-L3r1ujeH5Ss7CLthXKM008" False) ((:+:) * (C1 * (MetaCons "OrderAsc" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a))) (C1 * (MetaCons "OrderDesc" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a))))
type Info (OrderDirection a) Source # 
type Info (OrderDirection a) = a

data NullPosition a Source #

Constructors

NullsFirst a 
NullsLast a 
NullsAuto a 

Instances

Functor NullPosition Source # 

Methods

fmap :: (a -> b) -> NullPosition a -> NullPosition b #

(<$) :: a -> NullPosition b -> NullPosition a #

Foldable NullPosition Source # 

Methods

fold :: Monoid m => NullPosition m -> m #

foldMap :: Monoid m => (a -> m) -> NullPosition a -> m #

foldr :: (a -> b -> b) -> b -> NullPosition a -> b #

foldr' :: (a -> b -> b) -> b -> NullPosition a -> b #

foldl :: (b -> a -> b) -> b -> NullPosition a -> b #

foldl' :: (b -> a -> b) -> b -> NullPosition a -> b #

foldr1 :: (a -> a -> a) -> NullPosition a -> a #

foldl1 :: (a -> a -> a) -> NullPosition a -> a #

toList :: NullPosition a -> [a] #

null :: NullPosition a -> Bool #

length :: NullPosition a -> Int #

elem :: Eq a => a -> NullPosition a -> Bool #

maximum :: Ord a => NullPosition a -> a #

minimum :: Ord a => NullPosition a -> a #

sum :: Num a => NullPosition a -> a #

product :: Num a => NullPosition a -> a #

Traversable NullPosition Source # 

Methods

traverse :: Applicative f => (a -> f b) -> NullPosition a -> f (NullPosition b) #

sequenceA :: Applicative f => NullPosition (f a) -> f (NullPosition a) #

mapM :: Monad m => (a -> m b) -> NullPosition a -> m (NullPosition b) #

sequence :: Monad m => NullPosition (m a) -> m (NullPosition a) #

Eq a => Eq (NullPosition a) Source # 
Data a => Data (NullPosition a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NullPosition a -> c (NullPosition a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (NullPosition a) #

toConstr :: NullPosition a -> Constr #

dataTypeOf :: NullPosition a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (NullPosition a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NullPosition a)) #

gmapT :: (forall b. Data b => b -> b) -> NullPosition a -> NullPosition a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NullPosition a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NullPosition a -> r #

gmapQ :: (forall d. Data d => d -> u) -> NullPosition a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NullPosition a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NullPosition a -> m (NullPosition a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NullPosition a -> m (NullPosition a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NullPosition a -> m (NullPosition a) #

Ord a => Ord (NullPosition a) Source # 
Show a => Show (NullPosition a) Source # 
Generic (NullPosition a) Source # 

Associated Types

type Rep (NullPosition a) :: * -> * #

Methods

from :: NullPosition a -> Rep (NullPosition a) x #

to :: Rep (NullPosition a) x -> NullPosition a #

Arbitrary a => Arbitrary (NullPosition a) Source # 
ToJSON a => ToJSON (NullPosition a) Source # 
FromJSON a => FromJSON (NullPosition a) Source # 
HasInfo (NullPosition a) Source # 

Associated Types

type Info (NullPosition a) :: * Source #

type Rep (NullPosition a) Source # 
type Rep (NullPosition a) = D1 * (MetaData "NullPosition" "Database.Sql.Type.Query" "queryparser-0.1.0.1-L3r1ujeH5Ss7CLthXKM008" False) ((:+:) * (C1 * (MetaCons "NullsFirst" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a))) ((:+:) * (C1 * (MetaCons "NullsLast" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a))) (C1 * (MetaCons "NullsAuto" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)))))
type Info (NullPosition a) Source # 
type Info (NullPosition a) = a

data Offset a Source #

Constructors

Offset a Text 

Instances

Functor Offset Source # 

Methods

fmap :: (a -> b) -> Offset a -> Offset b #

(<$) :: a -> Offset b -> Offset a #

Foldable Offset Source # 

Methods

fold :: Monoid m => Offset m -> m #

foldMap :: Monoid m => (a -> m) -> Offset a -> m #

foldr :: (a -> b -> b) -> b -> Offset a -> b #

foldr' :: (a -> b -> b) -> b -> Offset a -> b #

foldl :: (b -> a -> b) -> b -> Offset a -> b #

foldl' :: (b -> a -> b) -> b -> Offset a -> b #

foldr1 :: (a -> a -> a) -> Offset a -> a #

foldl1 :: (a -> a -> a) -> Offset a -> a #

toList :: Offset a -> [a] #

null :: Offset a -> Bool #

length :: Offset a -> Int #

elem :: Eq a => a -> Offset a -> Bool #

maximum :: Ord a => Offset a -> a #

minimum :: Ord a => Offset a -> a #

sum :: Num a => Offset a -> a #

product :: Num a => Offset a -> a #

Traversable Offset Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Offset a -> f (Offset b) #

sequenceA :: Applicative f => Offset (f a) -> f (Offset a) #

mapM :: Monad m => (a -> m b) -> Offset a -> m (Offset b) #

sequence :: Monad m => Offset (m a) -> m (Offset a) #

Evaluation e => Evaluate e (Offset a) Source # 

Associated Types

type EvalResult e (Offset a) :: * Source #

Methods

eval :: Proxy * e -> Offset a -> EvalResult e (Offset a) Source #

Eq a => Eq (Offset a) Source # 

Methods

(==) :: Offset a -> Offset a -> Bool #

(/=) :: Offset a -> Offset a -> Bool #

Data a => Data (Offset a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Offset a -> c (Offset a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Offset a) #

toConstr :: Offset a -> Constr #

dataTypeOf :: Offset a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Offset a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Offset a)) #

gmapT :: (forall b. Data b => b -> b) -> Offset a -> Offset a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Offset a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Offset a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Offset a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Offset a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Offset a -> m (Offset a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Offset a -> m (Offset a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Offset a -> m (Offset a) #

Ord a => Ord (Offset a) Source # 

Methods

compare :: Offset a -> Offset a -> Ordering #

(<) :: Offset a -> Offset a -> Bool #

(<=) :: Offset a -> Offset a -> Bool #

(>) :: Offset a -> Offset a -> Bool #

(>=) :: Offset a -> Offset a -> Bool #

max :: Offset a -> Offset a -> Offset a #

min :: Offset a -> Offset a -> Offset a #

Show a => Show (Offset a) Source # 

Methods

showsPrec :: Int -> Offset a -> ShowS #

show :: Offset a -> String #

showList :: [Offset a] -> ShowS #

Generic (Offset a) Source # 

Associated Types

type Rep (Offset a) :: * -> * #

Methods

from :: Offset a -> Rep (Offset a) x #

to :: Rep (Offset a) x -> Offset a #

ToJSON a => ToJSON (Offset a) Source # 
FromJSON a => FromJSON (Offset a) Source # 
HasInfo (Offset a) Source # 

Associated Types

type Info (Offset a) :: * Source #

Methods

getInfo :: Offset a -> Info (Offset a) Source #

type EvalResult e (Offset a) Source # 
type EvalResult e (Offset a) = RecordSet e -> RecordSet e
type Rep (Offset a) Source # 
type Rep (Offset a) = D1 * (MetaData "Offset" "Database.Sql.Type.Query" "queryparser-0.1.0.1-L3r1ujeH5Ss7CLthXKM008" False) (C1 * (MetaCons "Offset" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text))))
type Info (Offset a) Source # 
type Info (Offset a) = a

data Limit a Source #

Constructors

Limit a Text 

Instances

Functor Limit Source # 

Methods

fmap :: (a -> b) -> Limit a -> Limit b #

(<$) :: a -> Limit b -> Limit a #

Foldable Limit Source # 

Methods

fold :: Monoid m => Limit m -> m #

foldMap :: Monoid m => (a -> m) -> Limit a -> m #

foldr :: (a -> b -> b) -> b -> Limit a -> b #

foldr' :: (a -> b -> b) -> b -> Limit a -> b #

foldl :: (b -> a -> b) -> b -> Limit a -> b #

foldl' :: (b -> a -> b) -> b -> Limit a -> b #

foldr1 :: (a -> a -> a) -> Limit a -> a #

foldl1 :: (a -> a -> a) -> Limit a -> a #

toList :: Limit a -> [a] #

null :: Limit a -> Bool #

length :: Limit a -> Int #

elem :: Eq a => a -> Limit a -> Bool #

maximum :: Ord a => Limit a -> a #

minimum :: Ord a => Limit a -> a #

sum :: Num a => Limit a -> a #

product :: Num a => Limit a -> a #

Traversable Limit Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Limit a -> f (Limit b) #

sequenceA :: Applicative f => Limit (f a) -> f (Limit a) #

mapM :: Monad m => (a -> m b) -> Limit a -> m (Limit b) #

sequence :: Monad m => Limit (m a) -> m (Limit a) #

Evaluation e => Evaluate e (Limit a) Source # 

Associated Types

type EvalResult e (Limit a) :: * Source #

Methods

eval :: Proxy * e -> Limit a -> EvalResult e (Limit a) Source #

Eq a => Eq (Limit a) Source # 

Methods

(==) :: Limit a -> Limit a -> Bool #

(/=) :: Limit a -> Limit a -> Bool #

Data a => Data (Limit a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Limit a -> c (Limit a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Limit a) #

toConstr :: Limit a -> Constr #

dataTypeOf :: Limit a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Limit a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Limit a)) #

gmapT :: (forall b. Data b => b -> b) -> Limit a -> Limit a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Limit a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Limit a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Limit a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Limit a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Limit a -> m (Limit a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Limit a -> m (Limit a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Limit a -> m (Limit a) #

Ord a => Ord (Limit a) Source # 

Methods

compare :: Limit a -> Limit a -> Ordering #

(<) :: Limit a -> Limit a -> Bool #

(<=) :: Limit a -> Limit a -> Bool #

(>) :: Limit a -> Limit a -> Bool #

(>=) :: Limit a -> Limit a -> Bool #

max :: Limit a -> Limit a -> Limit a #

min :: Limit a -> Limit a -> Limit a #

Show a => Show (Limit a) Source # 

Methods

showsPrec :: Int -> Limit a -> ShowS #

show :: Limit a -> String #

showList :: [Limit a] -> ShowS #

Generic (Limit a) Source # 

Associated Types

type Rep (Limit a) :: * -> * #

Methods

from :: Limit a -> Rep (Limit a) x #

to :: Rep (Limit a) x -> Limit a #

ToJSON a => ToJSON (Limit a) Source # 
FromJSON a => FromJSON (Limit a) Source # 
HasInfo (Limit a) Source # 

Associated Types

type Info (Limit a) :: * Source #

Methods

getInfo :: Limit a -> Info (Limit a) Source #

type EvalResult e (Limit a) Source # 
type EvalResult e (Limit a) = RecordSet e -> RecordSet e
type Rep (Limit a) Source # 
type Rep (Limit a) = D1 * (MetaData "Limit" "Database.Sql.Type.Query" "queryparser-0.1.0.1-L3r1ujeH5Ss7CLthXKM008" False) (C1 * (MetaCons "Limit" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text))))
type Info (Limit a) Source # 
type Info (Limit a) = a

data Selection r a Source #

Constructors

SelectStar a (Maybe (TableRef r a)) (StarReferents r a) 
SelectExpr a [ColumnAlias a] (Expr r a) 

Instances

Evaluation e => Evaluate e (Selection ResolvedNames Range) Source # 
ConstrainSASNames Functor r => Functor (Selection r) Source # 

Methods

fmap :: (a -> b) -> Selection r a -> Selection r b #

(<$) :: a -> Selection r b -> Selection r a #

ConstrainSASNames Foldable r => Foldable (Selection r) Source # 

Methods

fold :: Monoid m => Selection r m -> m #

foldMap :: Monoid m => (a -> m) -> Selection r a -> m #

foldr :: (a -> b -> b) -> b -> Selection r a -> b #

foldr' :: (a -> b -> b) -> b -> Selection r a -> b #

foldl :: (b -> a -> b) -> b -> Selection r a -> b #

foldl' :: (b -> a -> b) -> b -> Selection r a -> b #

foldr1 :: (a -> a -> a) -> Selection r a -> a #

foldl1 :: (a -> a -> a) -> Selection r a -> a #

toList :: Selection r a -> [a] #

null :: Selection r a -> Bool #

length :: Selection r a -> Int #

elem :: Eq a => a -> Selection r a -> Bool #

maximum :: Ord a => Selection r a -> a #

minimum :: Ord a => Selection r a -> a #

sum :: Num a => Selection r a -> a #

product :: Num a => Selection r a -> a #

ConstrainSASNames Traversable r => Traversable (Selection r) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Selection r a -> f (Selection r b) #

sequenceA :: Applicative f => Selection r (f a) -> f (Selection r a) #

mapM :: Monad m => (a -> m b) -> Selection r a -> m (Selection r b) #

sequence :: Monad m => Selection r (m a) -> m (Selection r a) #

ConstrainSNames Eq r a => Eq (Selection r a) Source # 

Methods

(==) :: Selection r a -> Selection r a -> Bool #

(/=) :: Selection r a -> Selection r a -> Bool #

(ConstrainSNames Data r a, Data r) => Data (Selection r a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Selection r a -> c (Selection r a) #

gunfold :: (forall b c. Data b => c (b -> c) -> c c) -> (forall b. b -> c b) -> Constr -> c (Selection r a) #

toConstr :: Selection r a -> Constr #

dataTypeOf :: Selection r a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Selection r a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Selection r a)) #

gmapT :: (forall b. Data b => b -> b) -> Selection r a -> Selection r a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Selection r a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Selection r a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Selection r a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Selection r a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Selection r a -> m (Selection r a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Selection r a -> m (Selection r a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Selection r a -> m (Selection r a) #

ConstrainSNames Ord r a => Ord (Selection r a) Source # 

Methods

compare :: Selection r a -> Selection r a -> Ordering #

(<) :: Selection r a -> Selection r a -> Bool #

(<=) :: Selection r a -> Selection r a -> Bool #

(>) :: Selection r a -> Selection r a -> Bool #

(>=) :: Selection r a -> Selection r a -> Bool #

max :: Selection r a -> Selection r a -> Selection r a #

min :: Selection r a -> Selection r a -> Selection r a #

ConstrainSNames Show r a => Show (Selection r a) Source # 

Methods

showsPrec :: Int -> Selection r a -> ShowS #

show :: Selection r a -> String #

showList :: [Selection r a] -> ShowS #

Generic (Selection r a) Source # 

Associated Types

type Rep (Selection r a) :: * -> * #

Methods

from :: Selection r a -> Rep (Selection r a) x #

to :: Rep (Selection r a) x -> Selection r a #

ConstrainSNames ToJSON r a => ToJSON (Selection r a) Source # 
ConstrainSNames FromJSON r a => FromJSON (Selection r a) Source # 
HasTables (Selection ResolvedNames a) Source # 
HasColumns (Selection ResolvedNames a) Source # 

Methods

goColumns :: Selection ResolvedNames a -> Observer Source #

HasInfo (Selection r a) Source # 

Associated Types

type Info (Selection r a) :: * Source #

Methods

getInfo :: Selection r a -> Info (Selection r a) Source #

type EvalResult e (Selection ResolvedNames Range) Source # 
type Rep (Selection r a) Source # 
type Info (Selection r a) Source # 
type Info (Selection r a) = a

data Constant a Source #

Constructors

StringConstant a ByteString

nb: Encoding *probably* matches server encoding, but there are ways to cram arbitrary byte sequences into strings on both Hive and Vertica.

NumericConstant a Text 
NullConstant a 
BooleanConstant a Bool 
TypedConstant a Text (DataType a) 
ParameterConstant a 

Instances

Functor Constant Source # 

Methods

fmap :: (a -> b) -> Constant a -> Constant b #

(<$) :: a -> Constant b -> Constant a #

Foldable Constant Source # 

Methods

fold :: Monoid m => Constant m -> m #

foldMap :: Monoid m => (a -> m) -> Constant a -> m #

foldr :: (a -> b -> b) -> b -> Constant a -> b #

foldr' :: (a -> b -> b) -> b -> Constant a -> b #

foldl :: (b -> a -> b) -> b -> Constant a -> b #

foldl' :: (b -> a -> b) -> b -> Constant a -> b #

foldr1 :: (a -> a -> a) -> Constant a -> a #

foldl1 :: (a -> a -> a) -> Constant a -> a #

toList :: Constant a -> [a] #

null :: Constant a -> Bool #

length :: Constant a -> Int #

elem :: Eq a => a -> Constant a -> Bool #

maximum :: Ord a => Constant a -> a #

minimum :: Ord a => Constant a -> a #

sum :: Num a => Constant a -> a #

product :: Num a => Constant a -> a #

Traversable Constant Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Constant a -> f (Constant b) #

sequenceA :: Applicative f => Constant (f a) -> f (Constant a) #

mapM :: Monad m => (a -> m b) -> Constant a -> m (Constant b) #

sequence :: Monad m => Constant (m a) -> m (Constant a) #

Evaluation e => Evaluate e (Constant a) Source # 

Associated Types

type EvalResult e (Constant a) :: * Source #

Methods

eval :: Proxy * e -> Constant a -> EvalResult e (Constant a) Source #

Eq a => Eq (Constant a) Source # 

Methods

(==) :: Constant a -> Constant a -> Bool #

(/=) :: Constant a -> Constant a -> Bool #

Data a => Data (Constant a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Constant a -> c (Constant a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Constant a) #

toConstr :: Constant a -> Constr #

dataTypeOf :: Constant a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Constant a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Constant a)) #

gmapT :: (forall b. Data b => b -> b) -> Constant a -> Constant a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Constant a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Constant a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Constant a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Constant a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Constant a -> m (Constant a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Constant a -> m (Constant a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Constant a -> m (Constant a) #

Ord a => Ord (Constant a) Source # 

Methods

compare :: Constant a -> Constant a -> Ordering #

(<) :: Constant a -> Constant a -> Bool #

(<=) :: Constant a -> Constant a -> Bool #

(>) :: Constant a -> Constant a -> Bool #

(>=) :: Constant a -> Constant a -> Bool #

max :: Constant a -> Constant a -> Constant a #

min :: Constant a -> Constant a -> Constant a #

Show a => Show (Constant a) Source # 

Methods

showsPrec :: Int -> Constant a -> ShowS #

show :: Constant a -> String #

showList :: [Constant a] -> ShowS #

Generic (Constant a) Source # 

Associated Types

type Rep (Constant a) :: * -> * #

Methods

from :: Constant a -> Rep (Constant a) x #

to :: Rep (Constant a) x -> Constant a #

Arbitrary a => Arbitrary (Constant a) Source # 

Methods

arbitrary :: Gen (Constant a) #

shrink :: Constant a -> [Constant a] #

ToJSON a => ToJSON (Constant a) Source # 
FromJSON a => FromJSON (Constant a) Source # 
HasInfo (Constant a) Source # 

Associated Types

type Info (Constant a) :: * Source #

Methods

getInfo :: Constant a -> Info (Constant a) Source #

type EvalResult e (Constant a) Source # 
type Rep (Constant a) Source # 
type Rep (Constant a) = D1 * (MetaData "Constant" "Database.Sql.Type.Query" "queryparser-0.1.0.1-L3r1ujeH5Ss7CLthXKM008" False) ((:+:) * ((:+:) * (C1 * (MetaCons "StringConstant" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ByteString)))) ((:+:) * (C1 * (MetaCons "NumericConstant" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))) (C1 * (MetaCons "NullConstant" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a))))) ((:+:) * (C1 * (MetaCons "BooleanConstant" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)))) ((:+:) * (C1 * (MetaCons "TypedConstant" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (DataType a)))))) (C1 * (MetaCons "ParameterConstant" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a))))))
type Info (Constant a) Source # 
type Info (Constant a) = a

data DataTypeParam a Source #

Instances

Functor DataTypeParam Source # 

Methods

fmap :: (a -> b) -> DataTypeParam a -> DataTypeParam b #

(<$) :: a -> DataTypeParam b -> DataTypeParam a #

Foldable DataTypeParam Source # 

Methods

fold :: Monoid m => DataTypeParam m -> m #

foldMap :: Monoid m => (a -> m) -> DataTypeParam a -> m #

foldr :: (a -> b -> b) -> b -> DataTypeParam a -> b #

foldr' :: (a -> b -> b) -> b -> DataTypeParam a -> b #

foldl :: (b -> a -> b) -> b -> DataTypeParam a -> b #

foldl' :: (b -> a -> b) -> b -> DataTypeParam a -> b #

foldr1 :: (a -> a -> a) -> DataTypeParam a -> a #

foldl1 :: (a -> a -> a) -> DataTypeParam a -> a #

toList :: DataTypeParam a -> [a] #

null :: DataTypeParam a -> Bool #

length :: DataTypeParam a -> Int #

elem :: Eq a => a -> DataTypeParam a -> Bool #

maximum :: Ord a => DataTypeParam a -> a #

minimum :: Ord a => DataTypeParam a -> a #

sum :: Num a => DataTypeParam a -> a #

product :: Num a => DataTypeParam a -> a #

Traversable DataTypeParam Source # 

Methods

traverse :: Applicative f => (a -> f b) -> DataTypeParam a -> f (DataTypeParam b) #

sequenceA :: Applicative f => DataTypeParam (f a) -> f (DataTypeParam a) #

mapM :: Monad m => (a -> m b) -> DataTypeParam a -> m (DataTypeParam b) #

sequence :: Monad m => DataTypeParam (m a) -> m (DataTypeParam a) #

Eq a => Eq (DataTypeParam a) Source # 
Data a => Data (DataTypeParam a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DataTypeParam a -> c (DataTypeParam a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DataTypeParam a) #

toConstr :: DataTypeParam a -> Constr #

dataTypeOf :: DataTypeParam a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (DataTypeParam a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DataTypeParam a)) #

gmapT :: (forall b. Data b => b -> b) -> DataTypeParam a -> DataTypeParam a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataTypeParam a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataTypeParam a -> r #

gmapQ :: (forall d. Data d => d -> u) -> DataTypeParam a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DataTypeParam a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataTypeParam a -> m (DataTypeParam a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataTypeParam a -> m (DataTypeParam a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataTypeParam a -> m (DataTypeParam a) #

Ord a => Ord (DataTypeParam a) Source # 
Show a => Show (DataTypeParam a) Source # 
Generic (DataTypeParam a) Source # 

Associated Types

type Rep (DataTypeParam a) :: * -> * #

ToJSON a => ToJSON (DataTypeParam a) Source # 
FromJSON a => FromJSON (DataTypeParam a) Source # 
HasInfo (DataTypeParam a) Source # 

Associated Types

type Info (DataTypeParam a) :: * Source #

type Rep (DataTypeParam a) Source # 
type Rep (DataTypeParam a) = D1 * (MetaData "DataTypeParam" "Database.Sql.Type.Query" "queryparser-0.1.0.1-L3r1ujeH5Ss7CLthXKM008" False) ((:+:) * (C1 * (MetaCons "DataTypeParamConstant" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Constant a)))) (C1 * (MetaCons "DataTypeParamType" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (DataType a)))))
type Info (DataTypeParam a) Source # 
type Info (DataTypeParam a) = a

data DataType a Source #

Instances

Functor DataType Source # 

Methods

fmap :: (a -> b) -> DataType a -> DataType b #

(<$) :: a -> DataType b -> DataType a #

Foldable DataType Source # 

Methods

fold :: Monoid m => DataType m -> m #

foldMap :: Monoid m => (a -> m) -> DataType a -> m #

foldr :: (a -> b -> b) -> b -> DataType a -> b #

foldr' :: (a -> b -> b) -> b -> DataType a -> b #

foldl :: (b -> a -> b) -> b -> DataType a -> b #

foldl' :: (b -> a -> b) -> b -> DataType a -> b #

foldr1 :: (a -> a -> a) -> DataType a -> a #

foldl1 :: (a -> a -> a) -> DataType a -> a #

toList :: DataType a -> [a] #

null :: DataType a -> Bool #

length :: DataType a -> Int #

elem :: Eq a => a -> DataType a -> Bool #

maximum :: Ord a => DataType a -> a #

minimum :: Ord a => DataType a -> a #

sum :: Num a => DataType a -> a #

product :: Num a => DataType a -> a #

Traversable DataType Source # 

Methods

traverse :: Applicative f => (a -> f b) -> DataType a -> f (DataType b) #

sequenceA :: Applicative f => DataType (f a) -> f (DataType a) #

mapM :: Monad m => (a -> m b) -> DataType a -> m (DataType b) #

sequence :: Monad m => DataType (m a) -> m (DataType a) #

Eq a => Eq (DataType a) Source # 

Methods

(==) :: DataType a -> DataType a -> Bool #

(/=) :: DataType a -> DataType a -> Bool #

Data a => Data (DataType a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DataType a -> c (DataType a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DataType a) #

toConstr :: DataType a -> Constr #

dataTypeOf :: DataType a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (DataType a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DataType a)) #

gmapT :: (forall b. Data b => b -> b) -> DataType a -> DataType a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataType a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataType a -> r #

gmapQ :: (forall d. Data d => d -> u) -> DataType a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DataType a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataType a -> m (DataType a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataType a -> m (DataType a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataType a -> m (DataType a) #

Ord a => Ord (DataType a) Source # 

Methods

compare :: DataType a -> DataType a -> Ordering #

(<) :: DataType a -> DataType a -> Bool #

(<=) :: DataType a -> DataType a -> Bool #

(>) :: DataType a -> DataType a -> Bool #

(>=) :: DataType a -> DataType a -> Bool #

max :: DataType a -> DataType a -> DataType a #

min :: DataType a -> DataType a -> DataType a #

Show a => Show (DataType a) Source # 

Methods

showsPrec :: Int -> DataType a -> ShowS #

show :: DataType a -> String #

showList :: [DataType a] -> ShowS #

Generic (DataType a) Source # 

Associated Types

type Rep (DataType a) :: * -> * #

Methods

from :: DataType a -> Rep (DataType a) x #

to :: Rep (DataType a) x -> DataType a #

ToJSON a => ToJSON (DataType a) Source # 
FromJSON a => FromJSON (DataType a) Source # 
HasInfo (DataType a) Source # 

Associated Types

type Info (DataType a) :: * Source #

Methods

getInfo :: DataType a -> Info (DataType a) Source #

type Rep (DataType a) Source # 
type Rep (DataType a) = D1 * (MetaData "DataType" "Database.Sql.Type.Query" "queryparser-0.1.0.1-L3r1ujeH5Ss7CLthXKM008" False) ((:+:) * ((:+:) * (C1 * (MetaCons "PrimitiveDataType" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [DataTypeParam a]))))) (C1 * (MetaCons "ArrayDataType" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (DataType a)))))) ((:+:) * (C1 * (MetaCons "MapDataType" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (DataType a))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (DataType a)))))) ((:+:) * (C1 * (MetaCons "StructDataType" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [(Text, DataType a)])))) (C1 * (MetaCons "UnionDataType" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [DataType a])))))))
type Info (DataType a) Source # 
type Info (DataType a) = a

data Operator a Source #

Constructors

Operator Text 

Instances

Functor Operator Source # 

Methods

fmap :: (a -> b) -> Operator a -> Operator b #

(<$) :: a -> Operator b -> Operator a #

Foldable Operator Source # 

Methods

fold :: Monoid m => Operator m -> m #

foldMap :: Monoid m => (a -> m) -> Operator a -> m #

foldr :: (a -> b -> b) -> b -> Operator a -> b #

foldr' :: (a -> b -> b) -> b -> Operator a -> b #

foldl :: (b -> a -> b) -> b -> Operator a -> b #

foldl' :: (b -> a -> b) -> b -> Operator a -> b #

foldr1 :: (a -> a -> a) -> Operator a -> a #

foldl1 :: (a -> a -> a) -> Operator a -> a #

toList :: Operator a -> [a] #

null :: Operator a -> Bool #

length :: Operator a -> Int #

elem :: Eq a => a -> Operator a -> Bool #

maximum :: Ord a => Operator a -> a #

minimum :: Ord a => Operator a -> a #

sum :: Num a => Operator a -> a #

product :: Num a => Operator a -> a #

Traversable Operator Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Operator a -> f (Operator b) #

sequenceA :: Applicative f => Operator (f a) -> f (Operator a) #

mapM :: Monad m => (a -> m b) -> Operator a -> m (Operator b) #

sequence :: Monad m => Operator (m a) -> m (Operator a) #

Eq (Operator a) Source # 

Methods

(==) :: Operator a -> Operator a -> Bool #

(/=) :: Operator a -> Operator a -> Bool #

Data a => Data (Operator a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Operator a -> c (Operator a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Operator a) #

toConstr :: Operator a -> Constr #

dataTypeOf :: Operator a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Operator a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Operator a)) #

gmapT :: (forall b. Data b => b -> b) -> Operator a -> Operator a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Operator a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Operator a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Operator a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Operator a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Operator a -> m (Operator a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Operator a -> m (Operator a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Operator a -> m (Operator a) #

Ord (Operator a) Source # 

Methods

compare :: Operator a -> Operator a -> Ordering #

(<) :: Operator a -> Operator a -> Bool #

(<=) :: Operator a -> Operator a -> Bool #

(>) :: Operator a -> Operator a -> Bool #

(>=) :: Operator a -> Operator a -> Bool #

max :: Operator a -> Operator a -> Operator a #

min :: Operator a -> Operator a -> Operator a #

Show (Operator a) Source # 

Methods

showsPrec :: Int -> Operator a -> ShowS #

show :: Operator a -> String #

showList :: [Operator a] -> ShowS #

IsString (Operator a) Source # 

Methods

fromString :: String -> Operator a #

Generic (Operator a) Source # 

Associated Types

type Rep (Operator a) :: * -> * #

Methods

from :: Operator a -> Rep (Operator a) x #

to :: Rep (Operator a) x -> Operator a #

ToJSON (Operator a) Source # 
FromJSON (Operator a) Source # 
type Rep (Operator a) Source # 
type Rep (Operator a) = D1 * (MetaData "Operator" "Database.Sql.Type.Query" "queryparser-0.1.0.1-L3r1ujeH5Ss7CLthXKM008" False) (C1 * (MetaCons "Operator" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

data ArrayIndex a Source #

Constructors

ArrayIndex a Text 

Instances

Functor ArrayIndex Source # 

Methods

fmap :: (a -> b) -> ArrayIndex a -> ArrayIndex b #

(<$) :: a -> ArrayIndex b -> ArrayIndex a #

Foldable ArrayIndex Source # 

Methods

fold :: Monoid m => ArrayIndex m -> m #

foldMap :: Monoid m => (a -> m) -> ArrayIndex a -> m #

foldr :: (a -> b -> b) -> b -> ArrayIndex a -> b #

foldr' :: (a -> b -> b) -> b -> ArrayIndex a -> b #

foldl :: (b -> a -> b) -> b -> ArrayIndex a -> b #

foldl' :: (b -> a -> b) -> b -> ArrayIndex a -> b #

foldr1 :: (a -> a -> a) -> ArrayIndex a -> a #

foldl1 :: (a -> a -> a) -> ArrayIndex a -> a #

toList :: ArrayIndex a -> [a] #

null :: ArrayIndex a -> Bool #

length :: ArrayIndex a -> Int #

elem :: Eq a => a -> ArrayIndex a -> Bool #

maximum :: Ord a => ArrayIndex a -> a #

minimum :: Ord a => ArrayIndex a -> a #

sum :: Num a => ArrayIndex a -> a #

product :: Num a => ArrayIndex a -> a #

Traversable ArrayIndex Source # 

Methods

traverse :: Applicative f => (a -> f b) -> ArrayIndex a -> f (ArrayIndex b) #

sequenceA :: Applicative f => ArrayIndex (f a) -> f (ArrayIndex a) #

mapM :: Monad m => (a -> m b) -> ArrayIndex a -> m (ArrayIndex b) #

sequence :: Monad m => ArrayIndex (m a) -> m (ArrayIndex a) #

Eq a => Eq (ArrayIndex a) Source # 

Methods

(==) :: ArrayIndex a -> ArrayIndex a -> Bool #

(/=) :: ArrayIndex a -> ArrayIndex a -> Bool #

Data a => Data (ArrayIndex a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ArrayIndex a -> c (ArrayIndex a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ArrayIndex a) #

toConstr :: ArrayIndex a -> Constr #

dataTypeOf :: ArrayIndex a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (ArrayIndex a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ArrayIndex a)) #

gmapT :: (forall b. Data b => b -> b) -> ArrayIndex a -> ArrayIndex a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArrayIndex a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArrayIndex a -> r #

gmapQ :: (forall d. Data d => d -> u) -> ArrayIndex a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ArrayIndex a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArrayIndex a -> m (ArrayIndex a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArrayIndex a -> m (ArrayIndex a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArrayIndex a -> m (ArrayIndex a) #

Ord a => Ord (ArrayIndex a) Source # 
Show a => Show (ArrayIndex a) Source # 
Generic (ArrayIndex a) Source # 

Associated Types

type Rep (ArrayIndex a) :: * -> * #

Methods

from :: ArrayIndex a -> Rep (ArrayIndex a) x #

to :: Rep (ArrayIndex a) x -> ArrayIndex a #

ToJSON a => ToJSON (ArrayIndex a) Source # 
FromJSON a => FromJSON (ArrayIndex a) Source # 
HasInfo (ArrayIndex a) Source # 

Associated Types

type Info (ArrayIndex a) :: * Source #

type Rep (ArrayIndex a) Source # 
type Rep (ArrayIndex a) = D1 * (MetaData "ArrayIndex" "Database.Sql.Type.Query" "queryparser-0.1.0.1-L3r1ujeH5Ss7CLthXKM008" False) (C1 * (MetaCons "ArrayIndex" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text))))
type Info (ArrayIndex a) Source # 
type Info (ArrayIndex a) = a

data Expr r a Source #

Constructors

BinOpExpr a (Operator a) (Expr r a) (Expr r a) 
CaseExpr a [(Expr r a, Expr r a)] (Maybe (Expr r a)) 
UnOpExpr a (Operator a) (Expr r a) 
LikeExpr a (Operator a) (Maybe (Escape r a)) (Pattern r a) (Expr r a) 
ConstantExpr a (Constant a) 
ColumnExpr a (ColumnRef r a) 
InListExpr a [Expr r a] (Expr r a) 
InSubqueryExpr a (Query r a) (Expr r a) 
BetweenExpr a (Expr r a) (Expr r a) (Expr r a) 
OverlapsExpr a (Expr r a, Expr r a) (Expr r a, Expr r a) 
FunctionExpr a (FunctionName a) Distinct [Expr r a] [(ParamName a, Expr r a)] (Maybe (Filter r a)) (Maybe (OverSubExpr r a)) 
AtTimeZoneExpr a (Expr r a) (Expr r a) 
SubqueryExpr a (Query r a) 
ArrayExpr a [Expr r a] 
ExistsExpr a (Query r a) 
FieldAccessExpr a (Expr r a) (StructFieldName a) 
ArrayAccessExpr a (Expr r a) (Expr r a) 
TypeCastExpr a CastFailureAction (Expr r a) (DataType a) 
VariableSubstitutionExpr a 

Instances

Evaluation e => Evaluate e (Expr ResolvedNames Range) Source # 
ConstrainSASNames Functor r => Functor (Expr r) Source # 

Methods

fmap :: (a -> b) -> Expr r a -> Expr r b #

(<$) :: a -> Expr r b -> Expr r a #

ConstrainSASNames Foldable r => Foldable (Expr r) Source # 

Methods

fold :: Monoid m => Expr r m -> m #

foldMap :: Monoid m => (a -> m) -> Expr r a -> m #

foldr :: (a -> b -> b) -> b -> Expr r a -> b #

foldr' :: (a -> b -> b) -> b -> Expr r a -> b #

foldl :: (b -> a -> b) -> b -> Expr r a -> b #

foldl' :: (b -> a -> b) -> b -> Expr r a -> b #

foldr1 :: (a -> a -> a) -> Expr r a -> a #

foldl1 :: (a -> a -> a) -> Expr r a -> a #

toList :: Expr r a -> [a] #

null :: Expr r a -> Bool #

length :: Expr r a -> Int #

elem :: Eq a => a -> Expr r a -> Bool #

maximum :: Ord a => Expr r a -> a #

minimum :: Ord a => Expr r a -> a #

sum :: Num a => Expr r a -> a #

product :: Num a => Expr r a -> a #

ConstrainSASNames Traversable r => Traversable (Expr r) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Expr r a -> f (Expr r b) #

sequenceA :: Applicative f => Expr r (f a) -> f (Expr r a) #

mapM :: Monad m => (a -> m b) -> Expr r a -> m (Expr r b) #

sequence :: Monad m => Expr r (m a) -> m (Expr r a) #

ConstrainSNames Eq r a => Eq (Expr r a) Source # 

Methods

(==) :: Expr r a -> Expr r a -> Bool #

(/=) :: Expr r a -> Expr r a -> Bool #

(ConstrainSNames Data r a, Data r) => Data (Expr r a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Expr r a -> c (Expr r a) #

gunfold :: (forall b c. Data b => c (b -> c) -> c c) -> (forall b. b -> c b) -> Constr -> c (Expr r a) #

toConstr :: Expr r a -> Constr #

dataTypeOf :: Expr r a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Expr r a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Expr r a)) #

gmapT :: (forall b. Data b => b -> b) -> Expr r a -> Expr r a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Expr r a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Expr r a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Expr r a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Expr r a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Expr r a -> m (Expr r a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Expr r a -> m (Expr r a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Expr r a -> m (Expr r a) #

ConstrainSNames Ord r a => Ord (Expr r a) Source # 

Methods

compare :: Expr r a -> Expr r a -> Ordering #

(<) :: Expr r a -> Expr r a -> Bool #

(<=) :: Expr r a -> Expr r a -> Bool #

(>) :: Expr r a -> Expr r a -> Bool #

(>=) :: Expr r a -> Expr r a -> Bool #

max :: Expr r a -> Expr r a -> Expr r a #

min :: Expr r a -> Expr r a -> Expr r a #

ConstrainSNames Show r a => Show (Expr r a) Source # 

Methods

showsPrec :: Int -> Expr r a -> ShowS #

show :: Expr r a -> String #

showList :: [Expr r a] -> ShowS #

Generic (Expr r a) Source # 

Associated Types

type Rep (Expr r a) :: * -> * #

Methods

from :: Expr r a -> Rep (Expr r a) x #

to :: Rep (Expr r a) x -> Expr r a #

(Arbitrary (PositionExpr r a), Arbitrary a) => Arbitrary (Expr r a) Source # 

Methods

arbitrary :: Gen (Expr r a) #

shrink :: Expr r a -> [Expr r a] #

ConstrainSNames ToJSON r a => ToJSON (Expr r a) Source # 

Methods

toJSON :: Expr r a -> Value #

toEncoding :: Expr r a -> Encoding #

toJSONList :: [Expr r a] -> Value #

toEncodingList :: [Expr r a] -> Encoding #

ConstrainSNames FromJSON r a => FromJSON (Expr r a) Source # 

Methods

parseJSON :: Value -> Parser (Expr r a) #

parseJSONList :: Value -> Parser [Expr r a] #

HasTables (Expr ResolvedNames a) Source # 
HasColumns (Expr ResolvedNames a) Source # 

Methods

goColumns :: Expr ResolvedNames a -> Observer Source #

HasInfo (Expr r a) Source # 

Associated Types

type Info (Expr r a) :: * Source #

Methods

getInfo :: Expr r a -> Info (Expr r a) Source #

type EvalResult e (Expr ResolvedNames Range) Source # 
type Rep (Expr r a) Source # 
type Rep (Expr r a) = D1 * (MetaData "Expr" "Database.Sql.Type.Query" "queryparser-0.1.0.1-L3r1ujeH5Ss7CLthXKM008" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "BinOpExpr" PrefixI False) ((:*:) * ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Operator a)))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Expr r a))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Expr r a)))))) (C1 * (MetaCons "CaseExpr" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [(Expr r a, Expr r a)])) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe (Expr r a)))))))) ((:+:) * (C1 * (MetaCons "UnOpExpr" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Operator a))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Expr r a)))))) (C1 * (MetaCons "LikeExpr" PrefixI False) ((:*:) * ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Operator a)))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe (Escape r a)))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Pattern r a))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Expr r a))))))))) ((:+:) * ((:+:) * (C1 * (MetaCons "ConstantExpr" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Constant a))))) (C1 * (MetaCons "ColumnExpr" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (ColumnRef r a)))))) ((:+:) * (C1 * (MetaCons "InListExpr" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Expr r a])) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Expr r a)))))) ((:+:) * (C1 * (MetaCons "InSubqueryExpr" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Query r a))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Expr r a)))))) (C1 * (MetaCons "BetweenExpr" PrefixI False) ((:*:) * ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Expr r a)))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Expr r a))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Expr r a)))))))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "OverlapsExpr" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Expr r a, Expr r a))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Expr r a, Expr r a)))))) (C1 * (MetaCons "FunctionExpr" PrefixI False) ((:*:) * ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (FunctionName a))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Distinct)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Expr r a])) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [(ParamName a, Expr r a)]))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe (Filter r a)))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe (OverSubExpr r a))))))))) ((:+:) * (C1 * (MetaCons "AtTimeZoneExpr" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Expr r a))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Expr r a)))))) ((:+:) * (C1 * (MetaCons "SubqueryExpr" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Query r a))))) (C1 * (MetaCons "ArrayExpr" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Expr r a]))))))) ((:+:) * ((:+:) * (C1 * (MetaCons "ExistsExpr" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Query r a))))) (C1 * (MetaCons "FieldAccessExpr" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Expr r a))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (StructFieldName a))))))) ((:+:) * (C1 * (MetaCons "ArrayAccessExpr" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Expr r a))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Expr r a)))))) ((:+:) * (C1 * (MetaCons "TypeCastExpr" PrefixI False) ((:*:) * ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CastFailureAction))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Expr r a))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (DataType a)))))) (C1 * (MetaCons "VariableSubstitutionExpr" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a))))))))
type Info (Expr r a) Source # 
type Info (Expr r a) = a

data CastFailureAction Source #

Instances

Eq CastFailureAction Source # 
Data CastFailureAction Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CastFailureAction -> c CastFailureAction #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CastFailureAction #

toConstr :: CastFailureAction -> Constr #

dataTypeOf :: CastFailureAction -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CastFailureAction) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CastFailureAction) #

gmapT :: (forall b. Data b => b -> b) -> CastFailureAction -> CastFailureAction #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CastFailureAction -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CastFailureAction -> r #

gmapQ :: (forall d. Data d => d -> u) -> CastFailureAction -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CastFailureAction -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CastFailureAction -> m CastFailureAction #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CastFailureAction -> m CastFailureAction #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CastFailureAction -> m CastFailureAction #

Ord CastFailureAction Source # 
Show CastFailureAction Source # 
Generic CastFailureAction Source # 
ToJSON CastFailureAction Source # 
FromJSON CastFailureAction Source # 
type Rep CastFailureAction Source # 
type Rep CastFailureAction = D1 * (MetaData "CastFailureAction" "Database.Sql.Type.Query" "queryparser-0.1.0.1-L3r1ujeH5Ss7CLthXKM008" False) ((:+:) * (C1 * (MetaCons "CastFailureToNull" PrefixI False) (U1 *)) (C1 * (MetaCons "CastFailureError" PrefixI False) (U1 *)))

newtype Escape r a Source #

Constructors

Escape 

Fields

Instances

ConstrainSASNames Functor r => Functor (Escape r) Source # 

Methods

fmap :: (a -> b) -> Escape r a -> Escape r b #

(<$) :: a -> Escape r b -> Escape r a #

ConstrainSASNames Foldable r => Foldable (Escape r) Source # 

Methods

fold :: Monoid m => Escape r m -> m #

foldMap :: Monoid m => (a -> m) -> Escape r a -> m #

foldr :: (a -> b -> b) -> b -> Escape r a -> b #

foldr' :: (a -> b -> b) -> b -> Escape r a -> b #

foldl :: (b -> a -> b) -> b -> Escape r a -> b #

foldl' :: (b -> a -> b) -> b -> Escape r a -> b #

foldr1 :: (a -> a -> a) -> Escape r a -> a #

foldl1 :: (a -> a -> a) -> Escape r a -> a #

toList :: Escape r a -> [a] #

null :: Escape r a -> Bool #

length :: Escape r a -> Int #

elem :: Eq a => a -> Escape r a -> Bool #

maximum :: Ord a => Escape r a -> a #

minimum :: Ord a => Escape r a -> a #

sum :: Num a => Escape r a -> a #

product :: Num a => Escape r a -> a #

ConstrainSASNames Traversable r => Traversable (Escape r) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Escape r a -> f (Escape r b) #

sequenceA :: Applicative f => Escape r (f a) -> f (Escape r a) #

mapM :: Monad m => (a -> m b) -> Escape r a -> m (Escape r b) #

sequence :: Monad m => Escape r (m a) -> m (Escape r a) #

ConstrainSNames Eq r a => Eq (Escape r a) Source # 

Methods

(==) :: Escape r a -> Escape r a -> Bool #

(/=) :: Escape r a -> Escape r a -> Bool #

(ConstrainSNames Data r a, Data r) => Data (Escape r a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Escape r a -> c (Escape r a) #

gunfold :: (forall b c. Data b => c (b -> c) -> c c) -> (forall b. b -> c b) -> Constr -> c (Escape r a) #

toConstr :: Escape r a -> Constr #

dataTypeOf :: Escape r a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Escape r a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Escape r a)) #

gmapT :: (forall b. Data b => b -> b) -> Escape r a -> Escape r a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Escape r a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Escape r a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Escape r a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Escape r a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Escape r a -> m (Escape r a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Escape r a -> m (Escape r a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Escape r a -> m (Escape r a) #

ConstrainSNames Ord r a => Ord (Escape r a) Source # 

Methods

compare :: Escape r a -> Escape r a -> Ordering #

(<) :: Escape r a -> Escape r a -> Bool #

(<=) :: Escape r a -> Escape r a -> Bool #

(>) :: Escape r a -> Escape r a -> Bool #

(>=) :: Escape r a -> Escape r a -> Bool #

max :: Escape r a -> Escape r a -> Escape r a #

min :: Escape r a -> Escape r a -> Escape r a #

ConstrainSNames Show r a => Show (Escape r a) Source # 

Methods

showsPrec :: Int -> Escape r a -> ShowS #

show :: Escape r a -> String #

showList :: [Escape r a] -> ShowS #

Generic (Escape r a) Source # 

Associated Types

type Rep (Escape r a) :: * -> * #

Methods

from :: Escape r a -> Rep (Escape r a) x #

to :: Rep (Escape r a) x -> Escape r a #

HasColumns (Escape ResolvedNames a) Source # 

Methods

goColumns :: Escape ResolvedNames a -> Observer Source #

HasInfo (Escape r a) Source # 

Associated Types

type Info (Escape r a) :: * Source #

Methods

getInfo :: Escape r a -> Info (Escape r a) Source #

type Rep (Escape r a) Source # 
type Rep (Escape r a) = D1 * (MetaData "Escape" "Database.Sql.Type.Query" "queryparser-0.1.0.1-L3r1ujeH5Ss7CLthXKM008" True) (C1 * (MetaCons "Escape" PrefixI True) (S1 * (MetaSel (Just Symbol "escapeExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Expr r a))))
type Info (Escape r a) Source # 
type Info (Escape r a) = a

newtype Pattern r a Source #

Constructors

Pattern 

Fields

Instances

ConstrainSASNames Functor r => Functor (Pattern r) Source # 

Methods

fmap :: (a -> b) -> Pattern r a -> Pattern r b #

(<$) :: a -> Pattern r b -> Pattern r a #

ConstrainSASNames Foldable r => Foldable (Pattern r) Source # 

Methods

fold :: Monoid m => Pattern r m -> m #

foldMap :: Monoid m => (a -> m) -> Pattern r a -> m #

foldr :: (a -> b -> b) -> b -> Pattern r a -> b #

foldr' :: (a -> b -> b) -> b -> Pattern r a -> b #

foldl :: (b -> a -> b) -> b -> Pattern r a -> b #

foldl' :: (b -> a -> b) -> b -> Pattern r a -> b #

foldr1 :: (a -> a -> a) -> Pattern r a -> a #

foldl1 :: (a -> a -> a) -> Pattern r a -> a #

toList :: Pattern r a -> [a] #

null :: Pattern r a -> Bool #

length :: Pattern r a -> Int #

elem :: Eq a => a -> Pattern r a -> Bool #

maximum :: Ord a => Pattern r a -> a #

minimum :: Ord a => Pattern r a -> a #

sum :: Num a => Pattern r a -> a #

product :: Num a => Pattern r a -> a #

ConstrainSASNames Traversable r => Traversable (Pattern r) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Pattern r a -> f (Pattern r b) #

sequenceA :: Applicative f => Pattern r (f a) -> f (Pattern r a) #

mapM :: Monad m => (a -> m b) -> Pattern r a -> m (Pattern r b) #

sequence :: Monad m => Pattern r (m a) -> m (Pattern r a) #

ConstrainSNames Eq r a => Eq (Pattern r a) Source # 

Methods

(==) :: Pattern r a -> Pattern r a -> Bool #

(/=) :: Pattern r a -> Pattern r a -> Bool #

(ConstrainSNames Data r a, Data r) => Data (Pattern r a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pattern r a -> c (Pattern r a) #

gunfold :: (forall b c. Data b => c (b -> c) -> c c) -> (forall b. b -> c b) -> Constr -> c (Pattern r a) #

toConstr :: Pattern r a -> Constr #

dataTypeOf :: Pattern r a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Pattern r a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Pattern r a)) #

gmapT :: (forall b. Data b => b -> b) -> Pattern r a -> Pattern r a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pattern r a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pattern r a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Pattern r a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Pattern r a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pattern r a -> m (Pattern r a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pattern r a -> m (Pattern r a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pattern r a -> m (Pattern r a) #

ConstrainSNames Ord r a => Ord (Pattern r a) Source # 

Methods

compare :: Pattern r a -> Pattern r a -> Ordering #

(<) :: Pattern r a -> Pattern r a -> Bool #

(<=) :: Pattern r a -> Pattern r a -> Bool #

(>) :: Pattern r a -> Pattern r a -> Bool #

(>=) :: Pattern r a -> Pattern r a -> Bool #

max :: Pattern r a -> Pattern r a -> Pattern r a #

min :: Pattern r a -> Pattern r a -> Pattern r a #

ConstrainSNames Show r a => Show (Pattern r a) Source # 

Methods

showsPrec :: Int -> Pattern r a -> ShowS #

show :: Pattern r a -> String #

showList :: [Pattern r a] -> ShowS #

Generic (Pattern r a) Source # 

Associated Types

type Rep (Pattern r a) :: * -> * #

Methods

from :: Pattern r a -> Rep (Pattern r a) x #

to :: Rep (Pattern r a) x -> Pattern r a #

HasColumns (Pattern ResolvedNames a) Source # 

Methods

goColumns :: Pattern ResolvedNames a -> Observer Source #

HasInfo (Pattern r a) Source # 

Associated Types

type Info (Pattern r a) :: * Source #

Methods

getInfo :: Pattern r a -> Info (Pattern r a) Source #

type Rep (Pattern r a) Source # 
type Rep (Pattern r a) = D1 * (MetaData "Pattern" "Database.Sql.Type.Query" "queryparser-0.1.0.1-L3r1ujeH5Ss7CLthXKM008" True) (C1 * (MetaCons "Pattern" PrefixI True) (S1 * (MetaSel (Just Symbol "patternExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Expr r a))))
type Info (Pattern r a) Source # 
type Info (Pattern r a) = a

data Filter r a Source #

Constructors

Filter 

Fields

Instances

ConstrainSASNames Functor r => Functor (Filter r) Source # 

Methods

fmap :: (a -> b) -> Filter r a -> Filter r b #

(<$) :: a -> Filter r b -> Filter r a #

ConstrainSASNames Foldable r => Foldable (Filter r) Source # 

Methods

fold :: Monoid m => Filter r m -> m #

foldMap :: Monoid m => (a -> m) -> Filter r a -> m #

foldr :: (a -> b -> b) -> b -> Filter r a -> b #

foldr' :: (a -> b -> b) -> b -> Filter r a -> b #

foldl :: (b -> a -> b) -> b -> Filter r a -> b #

foldl' :: (b -> a -> b) -> b -> Filter r a -> b #

foldr1 :: (a -> a -> a) -> Filter r a -> a #

foldl1 :: (a -> a -> a) -> Filter r a -> a #

toList :: Filter r a -> [a] #

null :: Filter r a -> Bool #

length :: Filter r a -> Int #

elem :: Eq a => a -> Filter r a -> Bool #

maximum :: Ord a => Filter r a -> a #

minimum :: Ord a => Filter r a -> a #

sum :: Num a => Filter r a -> a #

product :: Num a => Filter r a -> a #

ConstrainSASNames Traversable r => Traversable (Filter r) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Filter r a -> f (Filter r b) #

sequenceA :: Applicative f => Filter r (f a) -> f (Filter r a) #

mapM :: Monad m => (a -> m b) -> Filter r a -> m (Filter r b) #

sequence :: Monad m => Filter r (m a) -> m (Filter r a) #

ConstrainSNames Eq r a => Eq (Filter r a) Source # 

Methods

(==) :: Filter r a -> Filter r a -> Bool #

(/=) :: Filter r a -> Filter r a -> Bool #

(ConstrainSNames Data r a, Data r) => Data (Filter r a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Filter r a -> c (Filter r a) #

gunfold :: (forall b c. Data b => c (b -> c) -> c c) -> (forall b. b -> c b) -> Constr -> c (Filter r a) #

toConstr :: Filter r a -> Constr #

dataTypeOf :: Filter r a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Filter r a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Filter r a)) #

gmapT :: (forall b. Data b => b -> b) -> Filter r a -> Filter r a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Filter r a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Filter r a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Filter r a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Filter r a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Filter r a -> m (Filter r a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Filter r a -> m (Filter r a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Filter r a -> m (Filter r a) #

ConstrainSNames Ord r a => Ord (Filter r a) Source # 

Methods

compare :: Filter r a -> Filter r a -> Ordering #

(<) :: Filter r a -> Filter r a -> Bool #

(<=) :: Filter r a -> Filter r a -> Bool #

(>) :: Filter r a -> Filter r a -> Bool #

(>=) :: Filter r a -> Filter r a -> Bool #

max :: Filter r a -> Filter r a -> Filter r a #

min :: Filter r a -> Filter r a -> Filter r a #

ConstrainSNames Show r a => Show (Filter r a) Source # 

Methods

showsPrec :: Int -> Filter r a -> ShowS #

show :: Filter r a -> String #

showList :: [Filter r a] -> ShowS #

Generic (Filter r a) Source # 

Associated Types

type Rep (Filter r a) :: * -> * #

Methods

from :: Filter r a -> Rep (Filter r a) x #

to :: Rep (Filter r a) x -> Filter r a #

(Arbitrary (PositionExpr r a), Arbitrary a) => Arbitrary (Filter r a) Source # 

Methods

arbitrary :: Gen (Filter r a) #

shrink :: Filter r a -> [Filter r a] #

ConstrainSNames ToJSON r a => ToJSON (Filter r a) Source # 

Methods

toJSON :: Filter r a -> Value #

toEncoding :: Filter r a -> Encoding #

toJSONList :: [Filter r a] -> Value #

toEncodingList :: [Filter r a] -> Encoding #

ConstrainSNames FromJSON r a => FromJSON (Filter r a) Source # 

Methods

parseJSON :: Value -> Parser (Filter r a) #

parseJSONList :: Value -> Parser [Filter r a] #

HasTables (Filter ResolvedNames a) Source # 
HasColumns (Filter ResolvedNames a) Source # 

Methods

goColumns :: Filter ResolvedNames a -> Observer Source #

HasInfo (Filter r a) Source # 

Associated Types

type Info (Filter r a) :: * Source #

Methods

getInfo :: Filter r a -> Info (Filter r a) Source #

type Rep (Filter r a) Source # 
type Rep (Filter r a) = D1 * (MetaData "Filter" "Database.Sql.Type.Query" "queryparser-0.1.0.1-L3r1ujeH5Ss7CLthXKM008" False) (C1 * (MetaCons "Filter" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "filterInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Just Symbol "filterExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Expr r a)))))
type Info (Filter r a) Source # 
type Info (Filter r a) = a

data Partition r a Source #

Constructors

PartitionBy a [Expr r a] 
PartitionBest a 
PartitionNodes a 

Instances

ConstrainSASNames Functor r => Functor (Partition r) Source # 

Methods

fmap :: (a -> b) -> Partition r a -> Partition r b #

(<$) :: a -> Partition r b -> Partition r a #

ConstrainSASNames Foldable r => Foldable (Partition r) Source # 

Methods

fold :: Monoid m => Partition r m -> m #

foldMap :: Monoid m => (a -> m) -> Partition r a -> m #

foldr :: (a -> b -> b) -> b -> Partition r a -> b #

foldr' :: (a -> b -> b) -> b -> Partition r a -> b #

foldl :: (b -> a -> b) -> b -> Partition r a -> b #

foldl' :: (b -> a -> b) -> b -> Partition r a -> b #

foldr1 :: (a -> a -> a) -> Partition r a -> a #

foldl1 :: (a -> a -> a) -> Partition r a -> a #

toList :: Partition r a -> [a] #

null :: Partition r a -> Bool #

length :: Partition r a -> Int #

elem :: Eq a => a -> Partition r a -> Bool #

maximum :: Ord a => Partition r a -> a #

minimum :: Ord a => Partition r a -> a #

sum :: Num a => Partition r a -> a #

product :: Num a => Partition r a -> a #

ConstrainSASNames Traversable r => Traversable (Partition r) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Partition r a -> f (Partition r b) #

sequenceA :: Applicative f => Partition r (f a) -> f (Partition r a) #

mapM :: Monad m => (a -> m b) -> Partition r a -> m (Partition r b) #

sequence :: Monad m => Partition r (m a) -> m (Partition r a) #

ConstrainSNames Eq r a => Eq (Partition r a) Source # 

Methods

(==) :: Partition r a -> Partition r a -> Bool #

(/=) :: Partition r a -> Partition r a -> Bool #

(ConstrainSNames Data r a, Data r) => Data (Partition r a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Partition r a -> c (Partition r a) #

gunfold :: (forall b c. Data b => c (b -> c) -> c c) -> (forall b. b -> c b) -> Constr -> c (Partition r a) #

toConstr :: Partition r a -> Constr #

dataTypeOf :: Partition r a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Partition r a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Partition r a)) #

gmapT :: (forall b. Data b => b -> b) -> Partition r a -> Partition r a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Partition r a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Partition r a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Partition r a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Partition r a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Partition r a -> m (Partition r a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Partition r a -> m (Partition r a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Partition r a -> m (Partition r a) #

ConstrainSNames Ord r a => Ord (Partition r a) Source # 

Methods

compare :: Partition r a -> Partition r a -> Ordering #

(<) :: Partition r a -> Partition r a -> Bool #

(<=) :: Partition r a -> Partition r a -> Bool #

(>) :: Partition r a -> Partition r a -> Bool #

(>=) :: Partition r a -> Partition r a -> Bool #

max :: Partition r a -> Partition r a -> Partition r a #

min :: Partition r a -> Partition r a -> Partition r a #

ConstrainSNames Show r a => Show (Partition r a) Source # 

Methods

showsPrec :: Int -> Partition r a -> ShowS #

show :: Partition r a -> String #

showList :: [Partition r a] -> ShowS #

Generic (Partition r a) Source # 

Associated Types

type Rep (Partition r a) :: * -> * #

Methods

from :: Partition r a -> Rep (Partition r a) x #

to :: Rep (Partition r a) x -> Partition r a #

(Arbitrary (PositionExpr r a), Arbitrary a) => Arbitrary (Partition r a) Source # 

Methods

arbitrary :: Gen (Partition r a) #

shrink :: Partition r a -> [Partition r a] #

ConstrainSNames ToJSON r a => ToJSON (Partition r a) Source # 
ConstrainSNames FromJSON r a => FromJSON (Partition r a) Source # 
HasTables (Partition ResolvedNames a) Source # 
HasColumns (Partition ResolvedNames a) Source # 

Methods

goColumns :: Partition ResolvedNames a -> Observer Source #

HasInfo (Partition r a) Source # 

Associated Types

type Info (Partition r a) :: * Source #

Methods

getInfo :: Partition r a -> Info (Partition r a) Source #

type Rep (Partition r a) Source # 
type Info (Partition r a) Source # 
type Info (Partition r a) = a

data FrameType a Source #

Constructors

RowFrame a 
RangeFrame a 

Instances

Functor FrameType Source # 

Methods

fmap :: (a -> b) -> FrameType a -> FrameType b #

(<$) :: a -> FrameType b -> FrameType a #

Foldable FrameType Source # 

Methods

fold :: Monoid m => FrameType m -> m #

foldMap :: Monoid m => (a -> m) -> FrameType a -> m #

foldr :: (a -> b -> b) -> b -> FrameType a -> b #

foldr' :: (a -> b -> b) -> b -> FrameType a -> b #

foldl :: (b -> a -> b) -> b -> FrameType a -> b #

foldl' :: (b -> a -> b) -> b -> FrameType a -> b #

foldr1 :: (a -> a -> a) -> FrameType a -> a #

foldl1 :: (a -> a -> a) -> FrameType a -> a #

toList :: FrameType a -> [a] #

null :: FrameType a -> Bool #

length :: FrameType a -> Int #

elem :: Eq a => a -> FrameType a -> Bool #

maximum :: Ord a => FrameType a -> a #

minimum :: Ord a => FrameType a -> a #

sum :: Num a => FrameType a -> a #

product :: Num a => FrameType a -> a #

Traversable FrameType Source # 

Methods

traverse :: Applicative f => (a -> f b) -> FrameType a -> f (FrameType b) #

sequenceA :: Applicative f => FrameType (f a) -> f (FrameType a) #

mapM :: Monad m => (a -> m b) -> FrameType a -> m (FrameType b) #

sequence :: Monad m => FrameType (m a) -> m (FrameType a) #

Eq a => Eq (FrameType a) Source # 

Methods

(==) :: FrameType a -> FrameType a -> Bool #

(/=) :: FrameType a -> FrameType a -> Bool #

Data a => Data (FrameType a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FrameType a -> c (FrameType a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FrameType a) #

toConstr :: FrameType a -> Constr #

dataTypeOf :: FrameType a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (FrameType a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FrameType a)) #

gmapT :: (forall b. Data b => b -> b) -> FrameType a -> FrameType a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FrameType a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FrameType a -> r #

gmapQ :: (forall d. Data d => d -> u) -> FrameType a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FrameType a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FrameType a -> m (FrameType a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FrameType a -> m (FrameType a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FrameType a -> m (FrameType a) #

Ord a => Ord (FrameType a) Source # 
Show a => Show (FrameType a) Source # 
Generic (FrameType a) Source # 

Associated Types

type Rep (FrameType a) :: * -> * #

Methods

from :: FrameType a -> Rep (FrameType a) x #

to :: Rep (FrameType a) x -> FrameType a #

Arbitrary a => Arbitrary (FrameType a) Source # 

Methods

arbitrary :: Gen (FrameType a) #

shrink :: FrameType a -> [FrameType a] #

ToJSON a => ToJSON (FrameType a) Source # 
FromJSON a => FromJSON (FrameType a) Source # 
HasInfo (FrameType a) Source # 

Associated Types

type Info (FrameType a) :: * Source #

Methods

getInfo :: FrameType a -> Info (FrameType a) Source #

type Rep (FrameType a) Source # 
type Rep (FrameType a) = D1 * (MetaData "FrameType" "Database.Sql.Type.Query" "queryparser-0.1.0.1-L3r1ujeH5Ss7CLthXKM008" False) ((:+:) * (C1 * (MetaCons "RowFrame" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a))) (C1 * (MetaCons "RangeFrame" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a))))
type Info (FrameType a) Source # 
type Info (FrameType a) = a

data FrameBound a Source #

Constructors

Unbounded a 
CurrentRow a 
Preceding a (Constant a) 
Following a (Constant a) 

Instances

Functor FrameBound Source # 

Methods

fmap :: (a -> b) -> FrameBound a -> FrameBound b #

(<$) :: a -> FrameBound b -> FrameBound a #

Foldable FrameBound Source # 

Methods

fold :: Monoid m => FrameBound m -> m #

foldMap :: Monoid m => (a -> m) -> FrameBound a -> m #

foldr :: (a -> b -> b) -> b -> FrameBound a -> b #

foldr' :: (a -> b -> b) -> b -> FrameBound a -> b #

foldl :: (b -> a -> b) -> b -> FrameBound a -> b #

foldl' :: (b -> a -> b) -> b -> FrameBound a -> b #

foldr1 :: (a -> a -> a) -> FrameBound a -> a #

foldl1 :: (a -> a -> a) -> FrameBound a -> a #

toList :: FrameBound a -> [a] #

null :: FrameBound a -> Bool #

length :: FrameBound a -> Int #

elem :: Eq a => a -> FrameBound a -> Bool #

maximum :: Ord a => FrameBound a -> a #

minimum :: Ord a => FrameBound a -> a #

sum :: Num a => FrameBound a -> a #

product :: Num a => FrameBound a -> a #

Traversable FrameBound Source # 

Methods

traverse :: Applicative f => (a -> f b) -> FrameBound a -> f (FrameBound b) #

sequenceA :: Applicative f => FrameBound (f a) -> f (FrameBound a) #

mapM :: Monad m => (a -> m b) -> FrameBound a -> m (FrameBound b) #

sequence :: Monad m => FrameBound (m a) -> m (FrameBound a) #

Eq a => Eq (FrameBound a) Source # 

Methods

(==) :: FrameBound a -> FrameBound a -> Bool #

(/=) :: FrameBound a -> FrameBound a -> Bool #

Data a => Data (FrameBound a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FrameBound a -> c (FrameBound a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FrameBound a) #

toConstr :: FrameBound a -> Constr #

dataTypeOf :: FrameBound a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (FrameBound a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FrameBound a)) #

gmapT :: (forall b. Data b => b -> b) -> FrameBound a -> FrameBound a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FrameBound a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FrameBound a -> r #

gmapQ :: (forall d. Data d => d -> u) -> FrameBound a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FrameBound a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FrameBound a -> m (FrameBound a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FrameBound a -> m (FrameBound a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FrameBound a -> m (FrameBound a) #

Ord a => Ord (FrameBound a) Source # 
Show a => Show (FrameBound a) Source # 
Generic (FrameBound a) Source # 

Associated Types

type Rep (FrameBound a) :: * -> * #

Methods

from :: FrameBound a -> Rep (FrameBound a) x #

to :: Rep (FrameBound a) x -> FrameBound a #

Arbitrary a => Arbitrary (FrameBound a) Source # 
ToJSON a => ToJSON (FrameBound a) Source # 
FromJSON a => FromJSON (FrameBound a) Source # 
HasInfo (FrameBound a) Source # 

Associated Types

type Info (FrameBound a) :: * Source #

type Rep (FrameBound a) Source # 
type Info (FrameBound a) Source # 
type Info (FrameBound a) = a

data Frame a Source #

Constructors

Frame 

Instances

Functor Frame Source # 

Methods

fmap :: (a -> b) -> Frame a -> Frame b #

(<$) :: a -> Frame b -> Frame a #

Foldable Frame Source # 

Methods

fold :: Monoid m => Frame m -> m #

foldMap :: Monoid m => (a -> m) -> Frame a -> m #

foldr :: (a -> b -> b) -> b -> Frame a -> b #

foldr' :: (a -> b -> b) -> b -> Frame a -> b #

foldl :: (b -> a -> b) -> b -> Frame a -> b #

foldl' :: (b -> a -> b) -> b -> Frame a -> b #

foldr1 :: (a -> a -> a) -> Frame a -> a #

foldl1 :: (a -> a -> a) -> Frame a -> a #

toList :: Frame a -> [a] #

null :: Frame a -> Bool #

length :: Frame a -> Int #

elem :: Eq a => a -> Frame a -> Bool #

maximum :: Ord a => Frame a -> a #

minimum :: Ord a => Frame a -> a #

sum :: Num a => Frame a -> a #

product :: Num a => Frame a -> a #

Traversable Frame Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Frame a -> f (Frame b) #

sequenceA :: Applicative f => Frame (f a) -> f (Frame a) #

mapM :: Monad m => (a -> m b) -> Frame a -> m (Frame b) #

sequence :: Monad m => Frame (m a) -> m (Frame a) #

Eq a => Eq (Frame a) Source # 

Methods

(==) :: Frame a -> Frame a -> Bool #

(/=) :: Frame a -> Frame a -> Bool #

Data a => Data (Frame a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Frame a -> c (Frame a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Frame a) #

toConstr :: Frame a -> Constr #

dataTypeOf :: Frame a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Frame a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Frame a)) #

gmapT :: (forall b. Data b => b -> b) -> Frame a -> Frame a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Frame a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Frame a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Frame a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Frame a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Frame a -> m (Frame a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Frame a -> m (Frame a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Frame a -> m (Frame a) #

Ord a => Ord (Frame a) Source # 

Methods

compare :: Frame a -> Frame a -> Ordering #

(<) :: Frame a -> Frame a -> Bool #

(<=) :: Frame a -> Frame a -> Bool #

(>) :: Frame a -> Frame a -> Bool #

(>=) :: Frame a -> Frame a -> Bool #

max :: Frame a -> Frame a -> Frame a #

min :: Frame a -> Frame a -> Frame a #

Show a => Show (Frame a) Source # 

Methods

showsPrec :: Int -> Frame a -> ShowS #

show :: Frame a -> String #

showList :: [Frame a] -> ShowS #

Generic (Frame a) Source # 

Associated Types

type Rep (Frame a) :: * -> * #

Methods

from :: Frame a -> Rep (Frame a) x #

to :: Rep (Frame a) x -> Frame a #

Arbitrary a => Arbitrary (Frame a) Source # 

Methods

arbitrary :: Gen (Frame a) #

shrink :: Frame a -> [Frame a] #

ToJSON a => ToJSON (Frame a) Source # 
FromJSON a => FromJSON (Frame a) Source # 
HasInfo (Frame a) Source # 

Associated Types

type Info (Frame a) :: * Source #

Methods

getInfo :: Frame a -> Info (Frame a) Source #

type Rep (Frame a) Source # 
type Rep (Frame a) = D1 * (MetaData "Frame" "Database.Sql.Type.Query" "queryparser-0.1.0.1-L3r1ujeH5Ss7CLthXKM008" False) (C1 * (MetaCons "Frame" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "frameInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Just Symbol "frameType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (FrameType a)))) ((:*:) * (S1 * (MetaSel (Just Symbol "frameStart") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (FrameBound a))) (S1 * (MetaSel (Just Symbol "frameEnd") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe (FrameBound a)))))))
type Info (Frame a) Source # 
type Info (Frame a) = a

data OverSubExpr r a Source #

Instances

ConstrainSASNames Functor r => Functor (OverSubExpr r) Source # 

Methods

fmap :: (a -> b) -> OverSubExpr r a -> OverSubExpr r b #

(<$) :: a -> OverSubExpr r b -> OverSubExpr r a #

ConstrainSASNames Foldable r => Foldable (OverSubExpr r) Source # 

Methods

fold :: Monoid m => OverSubExpr r m -> m #

foldMap :: Monoid m => (a -> m) -> OverSubExpr r a -> m #

foldr :: (a -> b -> b) -> b -> OverSubExpr r a -> b #

foldr' :: (a -> b -> b) -> b -> OverSubExpr r a -> b #

foldl :: (b -> a -> b) -> b -> OverSubExpr r a -> b #

foldl' :: (b -> a -> b) -> b -> OverSubExpr r a -> b #

foldr1 :: (a -> a -> a) -> OverSubExpr r a -> a #

foldl1 :: (a -> a -> a) -> OverSubExpr r a -> a #

toList :: OverSubExpr r a -> [a] #

null :: OverSubExpr r a -> Bool #

length :: OverSubExpr r a -> Int #

elem :: Eq a => a -> OverSubExpr r a -> Bool #

maximum :: Ord a => OverSubExpr r a -> a #

minimum :: Ord a => OverSubExpr r a -> a #

sum :: Num a => OverSubExpr r a -> a #

product :: Num a => OverSubExpr r a -> a #

ConstrainSASNames Traversable r => Traversable (OverSubExpr r) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> OverSubExpr r a -> f (OverSubExpr r b) #

sequenceA :: Applicative f => OverSubExpr r (f a) -> f (OverSubExpr r a) #

mapM :: Monad m => (a -> m b) -> OverSubExpr r a -> m (OverSubExpr r b) #

sequence :: Monad m => OverSubExpr r (m a) -> m (OverSubExpr r a) #

ConstrainSNames Eq r a => Eq (OverSubExpr r a) Source # 

Methods

(==) :: OverSubExpr r a -> OverSubExpr r a -> Bool #

(/=) :: OverSubExpr r a -> OverSubExpr r a -> Bool #

(ConstrainSNames Data r a, Data r) => Data (OverSubExpr r a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OverSubExpr r a -> c (OverSubExpr r a) #

gunfold :: (forall b c. Data b => c (b -> c) -> c c) -> (forall b. b -> c b) -> Constr -> c (OverSubExpr r a) #

toConstr :: OverSubExpr r a -> Constr #

dataTypeOf :: OverSubExpr r a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (OverSubExpr r a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (OverSubExpr r a)) #

gmapT :: (forall b. Data b => b -> b) -> OverSubExpr r a -> OverSubExpr r a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OverSubExpr r a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OverSubExpr r a -> r #

gmapQ :: (forall d. Data d => d -> u) -> OverSubExpr r a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OverSubExpr r a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OverSubExpr r a -> m (OverSubExpr r a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OverSubExpr r a -> m (OverSubExpr r a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OverSubExpr r a -> m (OverSubExpr r a) #

ConstrainSNames Ord r a => Ord (OverSubExpr r a) Source # 

Methods

compare :: OverSubExpr r a -> OverSubExpr r a -> Ordering #

(<) :: OverSubExpr r a -> OverSubExpr r a -> Bool #

(<=) :: OverSubExpr r a -> OverSubExpr r a -> Bool #

(>) :: OverSubExpr r a -> OverSubExpr r a -> Bool #

(>=) :: OverSubExpr r a -> OverSubExpr r a -> Bool #

max :: OverSubExpr r a -> OverSubExpr r a -> OverSubExpr r a #

min :: OverSubExpr r a -> OverSubExpr r a -> OverSubExpr r a #

ConstrainSNames Show r a => Show (OverSubExpr r a) Source # 

Methods

showsPrec :: Int -> OverSubExpr r a -> ShowS #

show :: OverSubExpr r a -> String #

showList :: [OverSubExpr r a] -> ShowS #

Generic (OverSubExpr r a) Source # 

Associated Types

type Rep (OverSubExpr r a) :: * -> * #

Methods

from :: OverSubExpr r a -> Rep (OverSubExpr r a) x #

to :: Rep (OverSubExpr r a) x -> OverSubExpr r a #

(Arbitrary (PositionExpr r a), Arbitrary a) => Arbitrary (OverSubExpr r a) Source # 

Methods

arbitrary :: Gen (OverSubExpr r a) #

shrink :: OverSubExpr r a -> [OverSubExpr r a] #

ConstrainSNames ToJSON r a => ToJSON (OverSubExpr r a) Source # 
ConstrainSNames FromJSON r a => FromJSON (OverSubExpr r a) Source # 
HasTables (OverSubExpr ResolvedNames a) Source # 
HasColumns (OverSubExpr ResolvedNames a) Source # 

Methods

goColumns :: OverSubExpr ResolvedNames a -> Observer Source #

HasInfo (OverSubExpr r a) Source # 

Associated Types

type Info (OverSubExpr r a) :: * Source #

Methods

getInfo :: OverSubExpr r a -> Info (OverSubExpr r a) Source #

type Rep (OverSubExpr r a) Source # 
type Info (OverSubExpr r a) Source # 
type Info (OverSubExpr r a) = a

data WindowExpr r a Source #

Instances

ConstrainSASNames Functor r => Functor (WindowExpr r) Source # 

Methods

fmap :: (a -> b) -> WindowExpr r a -> WindowExpr r b #

(<$) :: a -> WindowExpr r b -> WindowExpr r a #

ConstrainSASNames Foldable r => Foldable (WindowExpr r) Source # 

Methods

fold :: Monoid m => WindowExpr r m -> m #

foldMap :: Monoid m => (a -> m) -> WindowExpr r a -> m #

foldr :: (a -> b -> b) -> b -> WindowExpr r a -> b #

foldr' :: (a -> b -> b) -> b -> WindowExpr r a -> b #

foldl :: (b -> a -> b) -> b -> WindowExpr r a -> b #

foldl' :: (b -> a -> b) -> b -> WindowExpr r a -> b #

foldr1 :: (a -> a -> a) -> WindowExpr r a -> a #

foldl1 :: (a -> a -> a) -> WindowExpr r a -> a #

toList :: WindowExpr r a -> [a] #

null :: WindowExpr r a -> Bool #

length :: WindowExpr r a -> Int #

elem :: Eq a => a -> WindowExpr r a -> Bool #

maximum :: Ord a => WindowExpr r a -> a #

minimum :: Ord a => WindowExpr r a -> a #

sum :: Num a => WindowExpr r a -> a #

product :: Num a => WindowExpr r a -> a #

ConstrainSASNames Traversable r => Traversable (WindowExpr r) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> WindowExpr r a -> f (WindowExpr r b) #

sequenceA :: Applicative f => WindowExpr r (f a) -> f (WindowExpr r a) #

mapM :: Monad m => (a -> m b) -> WindowExpr r a -> m (WindowExpr r b) #

sequence :: Monad m => WindowExpr r (m a) -> m (WindowExpr r a) #

ConstrainSNames Eq r a => Eq (WindowExpr r a) Source # 

Methods

(==) :: WindowExpr r a -> WindowExpr r a -> Bool #

(/=) :: WindowExpr r a -> WindowExpr r a -> Bool #

(ConstrainSNames Data r a, Data r) => Data (WindowExpr r a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WindowExpr r a -> c (WindowExpr r a) #

gunfold :: (forall b c. Data b => c (b -> c) -> c c) -> (forall b. b -> c b) -> Constr -> c (WindowExpr r a) #

toConstr :: WindowExpr r a -> Constr #

dataTypeOf :: WindowExpr r a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (WindowExpr r a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WindowExpr r a)) #

gmapT :: (forall b. Data b => b -> b) -> WindowExpr r a -> WindowExpr r a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WindowExpr r a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WindowExpr r a -> r #

gmapQ :: (forall d. Data d => d -> u) -> WindowExpr r a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WindowExpr r a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WindowExpr r a -> m (WindowExpr r a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WindowExpr r a -> m (WindowExpr r a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WindowExpr r a -> m (WindowExpr r a) #

ConstrainSNames Ord r a => Ord (WindowExpr r a) Source # 

Methods

compare :: WindowExpr r a -> WindowExpr r a -> Ordering #

(<) :: WindowExpr r a -> WindowExpr r a -> Bool #

(<=) :: WindowExpr r a -> WindowExpr r a -> Bool #

(>) :: WindowExpr r a -> WindowExpr r a -> Bool #

(>=) :: WindowExpr r a -> WindowExpr r a -> Bool #

max :: WindowExpr r a -> WindowExpr r a -> WindowExpr r a #

min :: WindowExpr r a -> WindowExpr r a -> WindowExpr r a #

ConstrainSNames Show r a => Show (WindowExpr r a) Source # 

Methods

showsPrec :: Int -> WindowExpr r a -> ShowS #

show :: WindowExpr r a -> String #

showList :: [WindowExpr r a] -> ShowS #

Generic (WindowExpr r a) Source # 

Associated Types

type Rep (WindowExpr r a) :: * -> * #

Methods

from :: WindowExpr r a -> Rep (WindowExpr r a) x #

to :: Rep (WindowExpr r a) x -> WindowExpr r a #

(Arbitrary (PositionExpr r a), Arbitrary a) => Arbitrary (WindowExpr r a) Source # 

Methods

arbitrary :: Gen (WindowExpr r a) #

shrink :: WindowExpr r a -> [WindowExpr r a] #

ConstrainSNames ToJSON r a => ToJSON (WindowExpr r a) Source # 
ConstrainSNames FromJSON r a => FromJSON (WindowExpr r a) Source # 
HasTables (WindowExpr ResolvedNames a) Source # 
HasColumns (WindowExpr ResolvedNames a) Source # 

Methods

goColumns :: WindowExpr ResolvedNames a -> Observer Source #

HasInfo (WindowExpr r a) Source # 

Associated Types

type Info (WindowExpr r a) :: * Source #

Methods

getInfo :: WindowExpr r a -> Info (WindowExpr r a) Source #

type Rep (WindowExpr r a) Source # 
type Rep (WindowExpr r a) = D1 * (MetaData "WindowExpr" "Database.Sql.Type.Query" "queryparser-0.1.0.1-L3r1ujeH5Ss7CLthXKM008" False) (C1 * (MetaCons "WindowExpr" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "windowExprInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Just Symbol "windowExprPartition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe (Partition r a))))) ((:*:) * (S1 * (MetaSel (Just Symbol "windowExprOrder") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Order r a])) (S1 * (MetaSel (Just Symbol "windowExprFrame") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe (Frame a)))))))
type Info (WindowExpr r a) Source # 
type Info (WindowExpr r a) = a

data PartialWindowExpr r a Source #

Instances

ConstrainSASNames Functor r => Functor (PartialWindowExpr r) Source # 

Methods

fmap :: (a -> b) -> PartialWindowExpr r a -> PartialWindowExpr r b #

(<$) :: a -> PartialWindowExpr r b -> PartialWindowExpr r a #

ConstrainSASNames Foldable r => Foldable (PartialWindowExpr r) Source # 

Methods

fold :: Monoid m => PartialWindowExpr r m -> m #

foldMap :: Monoid m => (a -> m) -> PartialWindowExpr r a -> m #

foldr :: (a -> b -> b) -> b -> PartialWindowExpr r a -> b #

foldr' :: (a -> b -> b) -> b -> PartialWindowExpr r a -> b #

foldl :: (b -> a -> b) -> b -> PartialWindowExpr r a -> b #

foldl' :: (b -> a -> b) -> b -> PartialWindowExpr r a -> b #

foldr1 :: (a -> a -> a) -> PartialWindowExpr r a -> a #

foldl1 :: (a -> a -> a) -> PartialWindowExpr r a -> a #

toList :: PartialWindowExpr r a -> [a] #

null :: PartialWindowExpr r a -> Bool #

length :: PartialWindowExpr r a -> Int #

elem :: Eq a => a -> PartialWindowExpr r a -> Bool #

maximum :: Ord a => PartialWindowExpr r a -> a #

minimum :: Ord a => PartialWindowExpr r a -> a #

sum :: Num a => PartialWindowExpr r a -> a #

product :: Num a => PartialWindowExpr r a -> a #

ConstrainSASNames Traversable r => Traversable (PartialWindowExpr r) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> PartialWindowExpr r a -> f (PartialWindowExpr r b) #

sequenceA :: Applicative f => PartialWindowExpr r (f a) -> f (PartialWindowExpr r a) #

mapM :: Monad m => (a -> m b) -> PartialWindowExpr r a -> m (PartialWindowExpr r b) #

sequence :: Monad m => PartialWindowExpr r (m a) -> m (PartialWindowExpr r a) #

ConstrainSNames Eq r a => Eq (PartialWindowExpr r a) Source # 
(ConstrainSNames Data r a, Data r) => Data (PartialWindowExpr r a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PartialWindowExpr r a -> c (PartialWindowExpr r a) #

gunfold :: (forall b c. Data b => c (b -> c) -> c c) -> (forall b. b -> c b) -> Constr -> c (PartialWindowExpr r a) #

toConstr :: PartialWindowExpr r a -> Constr #

dataTypeOf :: PartialWindowExpr r a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (PartialWindowExpr r a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PartialWindowExpr r a)) #

gmapT :: (forall b. Data b => b -> b) -> PartialWindowExpr r a -> PartialWindowExpr r a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PartialWindowExpr r a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PartialWindowExpr r a -> r #

gmapQ :: (forall d. Data d => d -> u) -> PartialWindowExpr r a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PartialWindowExpr r a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PartialWindowExpr r a -> m (PartialWindowExpr r a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PartialWindowExpr r a -> m (PartialWindowExpr r a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PartialWindowExpr r a -> m (PartialWindowExpr r a) #

ConstrainSNames Ord r a => Ord (PartialWindowExpr r a) Source # 
ConstrainSNames Show r a => Show (PartialWindowExpr r a) Source # 
Generic (PartialWindowExpr r a) Source # 

Associated Types

type Rep (PartialWindowExpr r a) :: * -> * #

(Arbitrary (PositionExpr r a), Arbitrary a) => Arbitrary (PartialWindowExpr r a) Source # 
ConstrainSNames ToJSON r a => ToJSON (PartialWindowExpr r a) Source # 
ConstrainSNames FromJSON r a => FromJSON (PartialWindowExpr r a) Source # 
HasTables (PartialWindowExpr ResolvedNames a) Source # 
HasColumns (PartialWindowExpr ResolvedNames a) Source # 
HasInfo (PartialWindowExpr r a) Source # 

Associated Types

type Info (PartialWindowExpr r a) :: * Source #

type Rep (PartialWindowExpr r a) Source # 
type Rep (PartialWindowExpr r a) = D1 * (MetaData "PartialWindowExpr" "Database.Sql.Type.Query" "queryparser-0.1.0.1-L3r1ujeH5Ss7CLthXKM008" False) (C1 * (MetaCons "PartialWindowExpr" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "partWindowExprInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Just Symbol "partWindowExprInherit") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (WindowName a)))) ((:*:) * (S1 * (MetaSel (Just Symbol "partWindowExprPartition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe (Partition r a)))) ((:*:) * (S1 * (MetaSel (Just Symbol "partWindowExprOrder") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Order r a])) (S1 * (MetaSel (Just Symbol "partWindowExprFrame") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe (Frame a))))))))
type Info (PartialWindowExpr r a) Source # 
type Info (PartialWindowExpr r a) = a

data WindowName a Source #

Constructors

WindowName a Text 

Instances

Functor WindowName Source # 

Methods

fmap :: (a -> b) -> WindowName a -> WindowName b #

(<$) :: a -> WindowName b -> WindowName a #

Foldable WindowName Source # 

Methods

fold :: Monoid m => WindowName m -> m #

foldMap :: Monoid m => (a -> m) -> WindowName a -> m #

foldr :: (a -> b -> b) -> b -> WindowName a -> b #

foldr' :: (a -> b -> b) -> b -> WindowName a -> b #

foldl :: (b -> a -> b) -> b -> WindowName a -> b #

foldl' :: (b -> a -> b) -> b -> WindowName a -> b #

foldr1 :: (a -> a -> a) -> WindowName a -> a #

foldl1 :: (a -> a -> a) -> WindowName a -> a #

toList :: WindowName a -> [a] #

null :: WindowName a -> Bool #

length :: WindowName a -> Int #

elem :: Eq a => a -> WindowName a -> Bool #

maximum :: Ord a => WindowName a -> a #

minimum :: Ord a => WindowName a -> a #

sum :: Num a => WindowName a -> a #

product :: Num a => WindowName a -> a #

Traversable WindowName Source # 

Methods

traverse :: Applicative f => (a -> f b) -> WindowName a -> f (WindowName b) #

sequenceA :: Applicative f => WindowName (f a) -> f (WindowName a) #

mapM :: Monad m => (a -> m b) -> WindowName a -> m (WindowName b) #

sequence :: Monad m => WindowName (m a) -> m (WindowName a) #

Eq a => Eq (WindowName a) Source # 

Methods

(==) :: WindowName a -> WindowName a -> Bool #

(/=) :: WindowName a -> WindowName a -> Bool #

Data a => Data (WindowName a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WindowName a -> c (WindowName a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WindowName a) #

toConstr :: WindowName a -> Constr #

dataTypeOf :: WindowName a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (WindowName a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WindowName a)) #

gmapT :: (forall b. Data b => b -> b) -> WindowName a -> WindowName a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WindowName a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WindowName a -> r #

gmapQ :: (forall d. Data d => d -> u) -> WindowName a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WindowName a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WindowName a -> m (WindowName a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WindowName a -> m (WindowName a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WindowName a -> m (WindowName a) #

Ord a => Ord (WindowName a) Source # 
Show a => Show (WindowName a) Source # 
Generic (WindowName a) Source # 

Associated Types

type Rep (WindowName a) :: * -> * #

Methods

from :: WindowName a -> Rep (WindowName a) x #

to :: Rep (WindowName a) x -> WindowName a #

Arbitrary a => Arbitrary (WindowName a) Source # 
ToJSON a => ToJSON (WindowName a) Source # 
FromJSON a => FromJSON (WindowName a) Source # 
HasInfo (WindowName a) Source # 

Associated Types

type Info (WindowName a) :: * Source #

type Rep (WindowName a) Source # 
type Rep (WindowName a) = D1 * (MetaData "WindowName" "Database.Sql.Type.Query" "queryparser-0.1.0.1-L3r1ujeH5Ss7CLthXKM008" False) (C1 * (MetaCons "WindowName" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text))))
type Info (WindowName a) Source # 
type Info (WindowName a) = a

data NamedWindowExpr r a Source #

Instances

ConstrainSASNames Functor r => Functor (NamedWindowExpr r) Source # 

Methods

fmap :: (a -> b) -> NamedWindowExpr r a -> NamedWindowExpr r b #

(<$) :: a -> NamedWindowExpr r b -> NamedWindowExpr r a #

ConstrainSASNames Foldable r => Foldable (NamedWindowExpr r) Source # 

Methods

fold :: Monoid m => NamedWindowExpr r m -> m #

foldMap :: Monoid m => (a -> m) -> NamedWindowExpr r a -> m #

foldr :: (a -> b -> b) -> b -> NamedWindowExpr r a -> b #

foldr' :: (a -> b -> b) -> b -> NamedWindowExpr r a -> b #

foldl :: (b -> a -> b) -> b -> NamedWindowExpr r a -> b #

foldl' :: (b -> a -> b) -> b -> NamedWindowExpr r a -> b #

foldr1 :: (a -> a -> a) -> NamedWindowExpr r a -> a #

foldl1 :: (a -> a -> a) -> NamedWindowExpr r a -> a #

toList :: NamedWindowExpr r a -> [a] #

null :: NamedWindowExpr r a -> Bool #

length :: NamedWindowExpr r a -> Int #

elem :: Eq a => a -> NamedWindowExpr r a -> Bool #

maximum :: Ord a => NamedWindowExpr r a -> a #

minimum :: Ord a => NamedWindowExpr r a -> a #

sum :: Num a => NamedWindowExpr r a -> a #

product :: Num a => NamedWindowExpr r a -> a #

ConstrainSASNames Traversable r => Traversable (NamedWindowExpr r) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> NamedWindowExpr r a -> f (NamedWindowExpr r b) #

sequenceA :: Applicative f => NamedWindowExpr r (f a) -> f (NamedWindowExpr r a) #

mapM :: Monad m => (a -> m b) -> NamedWindowExpr r a -> m (NamedWindowExpr r b) #

sequence :: Monad m => NamedWindowExpr r (m a) -> m (NamedWindowExpr r a) #

ConstrainSNames Eq r a => Eq (NamedWindowExpr r a) Source # 
(ConstrainSNames Data r a, Data r) => Data (NamedWindowExpr r a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NamedWindowExpr r a -> c (NamedWindowExpr r a) #

gunfold :: (forall b c. Data b => c (b -> c) -> c c) -> (forall b. b -> c b) -> Constr -> c (NamedWindowExpr r a) #

toConstr :: NamedWindowExpr r a -> Constr #

dataTypeOf :: NamedWindowExpr r a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (NamedWindowExpr r a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NamedWindowExpr r a)) #

gmapT :: (forall b. Data b => b -> b) -> NamedWindowExpr r a -> NamedWindowExpr r a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NamedWindowExpr r a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NamedWindowExpr r a -> r #

gmapQ :: (forall d. Data d => d -> u) -> NamedWindowExpr r a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NamedWindowExpr r a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NamedWindowExpr r a -> m (NamedWindowExpr r a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NamedWindowExpr r a -> m (NamedWindowExpr r a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NamedWindowExpr r a -> m (NamedWindowExpr r a) #

ConstrainSNames Ord r a => Ord (NamedWindowExpr r a) Source # 
ConstrainSNames Show r a => Show (NamedWindowExpr r a) Source # 
Generic (NamedWindowExpr r a) Source # 

Associated Types

type Rep (NamedWindowExpr r a) :: * -> * #

Methods

from :: NamedWindowExpr r a -> Rep (NamedWindowExpr r a) x #

to :: Rep (NamedWindowExpr r a) x -> NamedWindowExpr r a #

ConstrainSNames ToJSON r a => ToJSON (NamedWindowExpr r a) Source # 
ConstrainSNames FromJSON r a => FromJSON (NamedWindowExpr r a) Source # 
HasTables (NamedWindowExpr ResolvedNames a) Source # 
HasColumns (NamedWindowExpr ResolvedNames a) Source # 
HasInfo (NamedWindowExpr r a) Source # 

Associated Types

type Info (NamedWindowExpr r a) :: * Source #

type Rep (NamedWindowExpr r a) Source # 
type Info (NamedWindowExpr r a) Source # 
type Info (NamedWindowExpr r a) = a

scaleDown :: Int -> Gen a -> Gen a Source #