mirror of
https://github.com/khibino/haskell-relational-record.git
synced 2024-12-15 14:53:28 +03:00
Automated merge with git://github.com/khibino/haskell-relational-record
This commit is contained in:
commit
9f109c50f1
@ -31,6 +31,7 @@ library
|
|||||||
Database.Relational.Query.Monad.Class
|
Database.Relational.Query.Monad.Class
|
||||||
Database.Relational.Query.Monad.Trans.Ordering
|
Database.Relational.Query.Monad.Trans.Ordering
|
||||||
Database.Relational.Query.Monad.Trans.Aggregate
|
Database.Relational.Query.Monad.Trans.Aggregate
|
||||||
|
Database.Relational.Query.Monad.Trans.Restrict
|
||||||
Database.Relational.Query.Monad.Trans.Join
|
Database.Relational.Query.Monad.Trans.Join
|
||||||
Database.Relational.Query.Monad.Core
|
Database.Relational.Query.Monad.Core
|
||||||
Database.Relational.Query.Monad.Simple
|
Database.Relational.Query.Monad.Simple
|
||||||
@ -51,7 +52,8 @@ library
|
|||||||
Database.Relational.Query.Internal.AliasId
|
Database.Relational.Query.Internal.AliasId
|
||||||
Database.Relational.Query.Internal.ShowS
|
Database.Relational.Query.Internal.ShowS
|
||||||
Database.Relational.Query.Internal.Product
|
Database.Relational.Query.Internal.Product
|
||||||
Database.Relational.Query.Internal.Context
|
Database.Relational.Query.Internal.RestrictContext
|
||||||
|
Database.Relational.Query.Monad.Trans.JoinState
|
||||||
Database.Relational.Query.Internal.AggregatingContext
|
Database.Relational.Query.Internal.AggregatingContext
|
||||||
Database.Relational.Query.Internal.OrderingContext
|
Database.Relational.Query.Internal.OrderingContext
|
||||||
Database.Relational.Query.Monad.Qualify
|
Database.Relational.Query.Monad.Qualify
|
||||||
|
@ -0,0 +1,55 @@
|
|||||||
|
-- |
|
||||||
|
-- Module : Database.Relational.Query.Internal.Context
|
||||||
|
-- Copyright : 2013 Kei Hibino
|
||||||
|
-- License : BSD3
|
||||||
|
--
|
||||||
|
-- Maintainer : ex8k.hibino@gmail.com
|
||||||
|
-- Stability : experimental
|
||||||
|
-- Portability : unknown
|
||||||
|
--
|
||||||
|
-- This module provides context definition for
|
||||||
|
-- "Database.Relational.Query.Monad.Trans.Join" and
|
||||||
|
-- "Database.Relational.Query.Monad.Trans.Ordering".
|
||||||
|
module Database.Relational.Query.Internal.RestrictContext (
|
||||||
|
-- * Context of restriction
|
||||||
|
RestrictContext,
|
||||||
|
|
||||||
|
primeRestrictContext,
|
||||||
|
|
||||||
|
addRestriction,
|
||||||
|
|
||||||
|
composeWheres
|
||||||
|
) where
|
||||||
|
|
||||||
|
import Database.Relational.Query.Expr (Expr, fromTriBool, exprAnd)
|
||||||
|
import Database.Relational.Query.Expr.Unsafe (showExpr)
|
||||||
|
|
||||||
|
import Database.Relational.Query.Projection (Projection)
|
||||||
|
|
||||||
|
import Language.SQL.Keyword (Keyword(..), unwordsSQL)
|
||||||
|
import qualified Language.SQL.Keyword as SQL
|
||||||
|
|
||||||
|
|
||||||
|
-- | Context type for Restrict.
|
||||||
|
data RestrictContext =
|
||||||
|
RestrictContext
|
||||||
|
{ restriction :: Maybe (Expr Projection Bool) }
|
||||||
|
|
||||||
|
-- | Initial 'RestrictContext'.
|
||||||
|
primeRestrictContext :: RestrictContext
|
||||||
|
primeRestrictContext = RestrictContext Nothing
|
||||||
|
|
||||||
|
-- | Add restriction of 'RestrictContext'.
|
||||||
|
addRestriction :: Expr Projection (Maybe Bool) -> RestrictContext -> RestrictContext
|
||||||
|
addRestriction e1 ctx =
|
||||||
|
ctx { restriction = Just . uf . restriction $ ctx }
|
||||||
|
where uf Nothing = fromTriBool e1
|
||||||
|
uf (Just e0) = e0 `exprAnd` fromTriBool e1
|
||||||
|
|
||||||
|
-- | Compose SQL String from QueryJoin monad object.
|
||||||
|
composeWheres' :: Maybe (Expr Projection Bool) -> String
|
||||||
|
composeWheres' = maybe [] (\e -> unwordsSQL [WHERE, SQL.word . showExpr $ e])
|
||||||
|
|
||||||
|
-- | Compose SQL String from QueryJoin monad object.
|
||||||
|
composeWheres :: RestrictContext -> String
|
||||||
|
composeWheres = composeWheres' . restriction
|
@ -32,10 +32,12 @@ import Database.Relational.Query.Sub (SubQuery, subQuery)
|
|||||||
|
|
||||||
import Database.Relational.Query.Monad.Qualify (Qualify)
|
import Database.Relational.Query.Monad.Qualify (Qualify)
|
||||||
import Database.Relational.Query.Monad.Class (MonadQualify(..))
|
import Database.Relational.Query.Monad.Class (MonadQualify(..))
|
||||||
import Database.Relational.Query.Monad.Trans.Join (QueryJoin, join')
|
import Database.Relational.Query.Monad.Trans.Join (join')
|
||||||
import qualified Database.Relational.Query.Monad.Trans.Join as Join
|
import qualified Database.Relational.Query.Monad.Trans.Join as Join
|
||||||
import Database.Relational.Query.Monad.Trans.Ordering (Orderings, orderings, OrderedQuery)
|
import Database.Relational.Query.Monad.Trans.Ordering (Orderings, orderings, OrderedQuery, OrderByAppend, orderByAppend)
|
||||||
import qualified Database.Relational.Query.Monad.Trans.Ordering as Ordering
|
import qualified Database.Relational.Query.Monad.Trans.Ordering as Ordering
|
||||||
|
import Database.Relational.Query.Monad.Trans.Restrict (restrict, WheresAppend, wheresAppend)
|
||||||
|
import qualified Database.Relational.Query.Monad.Trans.Restrict as Restrict
|
||||||
import Database.Relational.Query.Monad.Core (QueryCore)
|
import Database.Relational.Query.Monad.Core (QueryCore)
|
||||||
import Database.Relational.Query.Monad.Trans.Aggregate (Aggregatings, aggregate, appendGroupBys)
|
import Database.Relational.Query.Monad.Trans.Aggregate (Aggregatings, aggregate, appendGroupBys)
|
||||||
|
|
||||||
@ -48,27 +50,27 @@ type AggregatedQuery r = OrderedQuery Aggregation (Aggregatings QueryCore) r
|
|||||||
|
|
||||||
-- | Lift from qualified table forms into 'QueryAggregate'.
|
-- | Lift from qualified table forms into 'QueryAggregate'.
|
||||||
aggregatedQuery :: Qualify a -> QueryAggregate a
|
aggregatedQuery :: Qualify a -> QueryAggregate a
|
||||||
aggregatedQuery = orderings . aggregate . join'
|
aggregatedQuery = orderings . aggregate . restrict . join'
|
||||||
|
|
||||||
-- | Instance to lift from qualified table forms into 'QueryAggregate'.
|
-- | Instance to lift from qualified table forms into 'QueryAggregate'.
|
||||||
instance MonadQualify Qualify (Orderings Aggregation (Aggregatings (QueryJoin Qualify))) where
|
instance MonadQualify Qualify (Orderings Aggregation (Aggregatings QueryCore)) where
|
||||||
liftQualify = aggregatedQuery
|
liftQualify = aggregatedQuery
|
||||||
|
|
||||||
-- | Run 'AggregatedQuery' to get SQL string.
|
-- | Run 'AggregatedQuery' to get SQL string.
|
||||||
expandSQL :: AggregatedQuery r -> Qualify ((String, Projection r), (String -> String, String -> String))
|
expandSQL :: AggregatedQuery r -> Qualify ((String, Projection r), ((OrderByAppend, String -> String), WheresAppend))
|
||||||
expandSQL q = Join.expandSQL $ assoc <$> appendGroupBys (Ordering.appendOrderBys q) where
|
expandSQL q = Join.expandSQL $ assoc <$> Restrict.appendWheres (appendGroupBys (Ordering.appendOrderBys q)) where
|
||||||
assoc ((a, b), c) = (Aggregation.unsafeProjection a, (b, c))
|
assoc (((a, b), c), d) = (Aggregation.unsafeProjection a, ((b, c), d))
|
||||||
|
|
||||||
-- | Run 'AggregatedQuery' to get SQL with 'Qualify' computation.
|
-- | Run 'AggregatedQuery' to get SQL with 'Qualify' computation.
|
||||||
toSQL :: AggregatedQuery r -- ^ 'AggregatedQuery' to run
|
toSQL :: AggregatedQuery r -- ^ 'AggregatedQuery' to run
|
||||||
-> Qualify String -- ^ Result SQL string with 'Qualify' computation
|
-> Qualify String -- ^ Result SQL string with 'Qualify' computation
|
||||||
toSQL q = do
|
toSQL q = do
|
||||||
((sql, _pj), (appOrd, appGrp)) <- expandSQL q
|
((sql, _pj), ((appOrd, appGrp), appWhere)) <- expandSQL q
|
||||||
return . appOrd $ appGrp sql
|
return . orderByAppend appOrd . appGrp . wheresAppend appWhere $ sql
|
||||||
|
|
||||||
-- | Run 'AggregatedQuery' to get 'SubQuery' with 'Qualify' computation.
|
-- | Run 'AggregatedQuery' to get 'SubQuery' with 'Qualify' computation.
|
||||||
toSubQuery :: AggregatedQuery r -- ^ 'AggregatedQuery' to run
|
toSubQuery :: AggregatedQuery r -- ^ 'AggregatedQuery' to run
|
||||||
-> Qualify SubQuery -- ^ Result 'SubQuery' with 'Qualify' computation
|
-> Qualify SubQuery -- ^ Result 'SubQuery' with 'Qualify' computation
|
||||||
toSubQuery q = do
|
toSubQuery q = do
|
||||||
((sql, pj), (appOrd, appGrp)) <- expandSQL q
|
((sql, pj), ((appOrd, appGrp), appWhere)) <- expandSQL q
|
||||||
return $ subQuery (appOrd $ appGrp sql) (Projection.width pj)
|
return $ subQuery (orderByAppend appOrd . appGrp . wheresAppend appWhere $ sql) (Projection.width pj)
|
||||||
|
@ -13,7 +13,7 @@
|
|||||||
-- This module defines query building interface classes.
|
-- This module defines query building interface classes.
|
||||||
module Database.Relational.Query.Monad.Class (
|
module Database.Relational.Query.Monad.Class (
|
||||||
-- * Query interface classes
|
-- * Query interface classes
|
||||||
MonadQualify (..),
|
MonadQualify (..), MonadRestrict (..),
|
||||||
MonadQuery (..), MonadAggregate (..),
|
MonadQuery (..), MonadAggregate (..),
|
||||||
|
|
||||||
onE, on, wheresE, wheres,
|
onE, on, wheresE, wheres,
|
||||||
@ -28,14 +28,20 @@ import Database.Relational.Query.Sub (SubQuery, Qualified)
|
|||||||
|
|
||||||
import Database.Relational.Query.Internal.Product (NodeAttr)
|
import Database.Relational.Query.Internal.Product (NodeAttr)
|
||||||
|
|
||||||
|
-- | Restrict context interface
|
||||||
|
class (Functor m, Monad m) => MonadRestrict m where
|
||||||
|
-- | Add restriction to this context.
|
||||||
|
restrictContext :: Expr Projection (Maybe Bool) -- ^ 'Expr' 'Projection' which represent restriction
|
||||||
|
-> m () -- ^ Restricted query context
|
||||||
|
|
||||||
-- | Query building interface.
|
-- | Query building interface.
|
||||||
class (Functor m, Monad m) => MonadQuery m where
|
class (Functor m, Monad m) => MonadQuery m where
|
||||||
-- | Add restriction to last join.
|
-- | Add restriction to last join.
|
||||||
restrictJoin :: Expr Projection (Maybe Bool) -- ^ 'Expr' 'Projection' which represent restriction
|
restrictJoin :: Expr Projection (Maybe Bool) -- ^ 'Expr' 'Projection' which represent restriction
|
||||||
-> m () -- ^ Restricted query context
|
-> m () -- ^ Restricted query context
|
||||||
-- | Add restriction to this query.
|
-- -- | Add restriction to this query.
|
||||||
restrictQuery :: Expr Projection (Maybe Bool) -- ^ 'Expr' 'Projection' which represent restriction
|
-- restrictQuery :: Expr Projection (Maybe Bool) -- ^ 'Expr' 'Projection' which represent restriction
|
||||||
-> m () -- ^ Restricted query context
|
-- -> m () -- ^ Restricted query context
|
||||||
-- | Unsafely join subquery with this query.
|
-- | Unsafely join subquery with this query.
|
||||||
unsafeSubQuery :: NodeAttr -- ^ Attribute maybe or just
|
unsafeSubQuery :: NodeAttr -- ^ Attribute maybe or just
|
||||||
-> Qualified SubQuery -- ^ 'SubQuery' to join
|
-> Qualified SubQuery -- ^ 'SubQuery' to join
|
||||||
@ -66,12 +72,12 @@ on :: MonadQuery m => Projection (Maybe Bool) -> m ()
|
|||||||
on = restrictJoin . expr
|
on = restrictJoin . expr
|
||||||
|
|
||||||
-- | Add restriction to this query.
|
-- | Add restriction to this query.
|
||||||
wheresE :: MonadQuery m => Expr Projection (Maybe Bool) -> m ()
|
wheresE :: MonadRestrict m => Expr Projection (Maybe Bool) -> m ()
|
||||||
wheresE = restrictQuery
|
wheresE = restrictContext
|
||||||
|
|
||||||
-- | Add restriction to this query. Projection type version.
|
-- | Add restriction to this query. Projection type version.
|
||||||
wheres :: MonadQuery m => Projection (Maybe Bool) -> m ()
|
wheres :: MonadRestrict m => Projection (Maybe Bool) -> m ()
|
||||||
wheres = restrictQuery . expr
|
wheres = restrictContext . expr
|
||||||
|
|
||||||
-- | Add /group by/ term into context and get aggregated projection.
|
-- | Add /group by/ term into context and get aggregated projection.
|
||||||
groupBy :: MonadAggregate m
|
groupBy :: MonadAggregate m
|
||||||
|
@ -15,7 +15,8 @@ module Database.Relational.Query.Monad.Core (
|
|||||||
|
|
||||||
import Database.Relational.Query.Monad.Qualify (Qualify)
|
import Database.Relational.Query.Monad.Qualify (Qualify)
|
||||||
import Database.Relational.Query.Monad.Trans.Join (QueryJoin)
|
import Database.Relational.Query.Monad.Trans.Join (QueryJoin)
|
||||||
|
import Database.Relational.Query.Monad.Trans.Restrict (Restrict)
|
||||||
|
|
||||||
|
|
||||||
-- | Core query monad type used by simple query and aggregated query.
|
-- | Core query monad type used by simple query and aggregated query.
|
||||||
type QueryCore = QueryJoin Qualify
|
type QueryCore = Restrict (QueryJoin Qualify)
|
||||||
|
@ -29,8 +29,11 @@ import Database.Relational.Query.Monad.Qualify (Qualify)
|
|||||||
import Database.Relational.Query.Monad.Class (MonadQualify(..))
|
import Database.Relational.Query.Monad.Class (MonadQualify(..))
|
||||||
import Database.Relational.Query.Monad.Trans.Join (join')
|
import Database.Relational.Query.Monad.Trans.Join (join')
|
||||||
import qualified Database.Relational.Query.Monad.Trans.Join as Join
|
import qualified Database.Relational.Query.Monad.Trans.Join as Join
|
||||||
import Database.Relational.Query.Monad.Trans.Ordering (Orderings, orderings, OrderedQuery)
|
import Database.Relational.Query.Monad.Trans.Ordering
|
||||||
|
(Orderings, orderings, OrderedQuery, OrderByAppend, orderByAppend)
|
||||||
import qualified Database.Relational.Query.Monad.Trans.Ordering as Ordering
|
import qualified Database.Relational.Query.Monad.Trans.Ordering as Ordering
|
||||||
|
import Database.Relational.Query.Monad.Trans.Restrict (restrict, WheresAppend, wheresAppend)
|
||||||
|
import qualified Database.Relational.Query.Monad.Trans.Restrict as Restrict
|
||||||
import Database.Relational.Query.Monad.Core (QueryCore)
|
import Database.Relational.Query.Monad.Core (QueryCore)
|
||||||
|
|
||||||
import Database.Relational.Query.Sub (SubQuery, subQuery)
|
import Database.Relational.Query.Sub (SubQuery, subQuery)
|
||||||
@ -44,27 +47,31 @@ type SimpleQuery r = OrderedQuery Projection QueryCore r
|
|||||||
|
|
||||||
-- | Lift from qualified table forms into 'QuerySimple'.
|
-- | Lift from qualified table forms into 'QuerySimple'.
|
||||||
simple :: Qualify a -> QuerySimple a
|
simple :: Qualify a -> QuerySimple a
|
||||||
simple = orderings . join'
|
simple = orderings . restrict . join'
|
||||||
|
|
||||||
-- | Instance to lift from qualified table forms into 'QuerySimple'.
|
-- | Instance to lift from qualified table forms into 'QuerySimple'.
|
||||||
instance MonadQualify Qualify (Orderings Projection QueryCore) where
|
instance MonadQualify Qualify (Orderings Projection QueryCore) where
|
||||||
liftQualify = simple
|
liftQualify = simple
|
||||||
|
|
||||||
-- | Run 'SimpleQuery' to get SQL string.
|
-- | Run 'SimpleQuery' to get SQL string.
|
||||||
expandSQL :: SimpleQuery r -- ^ 'SimpleQuery' to run
|
expandSQL' :: SimpleQuery r -- ^ 'SimpleQuery' to run
|
||||||
-> Qualify ((String, Projection r), String -> String) -- ^ Result SQL string and ordering appending function
|
-> Qualify ((String, Projection r), (OrderByAppend, WheresAppend)) -- ^ Result SQL string and ordering appending function
|
||||||
expandSQL = Join.expandSQL . Ordering.appendOrderBys
|
expandSQL' = Join.expandSQL . fmap assoc . Restrict.appendWheres . Ordering.appendOrderBys where
|
||||||
|
assoc ((a, b), c) = (a, (b, c))
|
||||||
|
|
||||||
|
expandSQL :: SimpleQuery r -> Qualify (String, Projection r)
|
||||||
|
expandSQL q = do
|
||||||
|
((sql, pj), (a1, a2)) <- expandSQL' q
|
||||||
|
return (orderByAppend a1 (wheresAppend a2 sql), pj)
|
||||||
|
|
||||||
-- | Run 'SimpleQuery' to get SQL string with 'Qualify' computation.
|
-- | Run 'SimpleQuery' to get SQL string with 'Qualify' computation.
|
||||||
toSQL :: SimpleQuery r -- ^ 'SimpleQuery' to run
|
toSQL :: SimpleQuery r -- ^ 'SimpleQuery' to run
|
||||||
-> Qualify String -- ^ Result SQL string with 'Qualify' computation
|
-> Qualify String -- ^ Result SQL string with 'Qualify' computation
|
||||||
toSQL q = do
|
toSQL q = fst `fmap` expandSQL q
|
||||||
((sql, _), append) <- expandSQL q
|
|
||||||
return $ append sql
|
|
||||||
|
|
||||||
-- | Run 'SimpleQuery' to get 'SubQuery' with 'Qualify' computation.
|
-- | Run 'SimpleQuery' to get 'SubQuery' with 'Qualify' computation.
|
||||||
toSubQuery :: SimpleQuery r -- ^ 'SimpleQuery' to run
|
toSubQuery :: SimpleQuery r -- ^ 'SimpleQuery' to run
|
||||||
-> Qualify SubQuery -- ^ Result 'SubQuery' with 'Qualify' computation
|
-> Qualify SubQuery -- ^ Result 'SubQuery' with 'Qualify' computation
|
||||||
toSubQuery q = do
|
toSubQuery q = do
|
||||||
((sql, pj), append) <- expandSQL q
|
(sql, pj) <- expandSQL q
|
||||||
return $ subQuery (append sql) (Projection.width pj)
|
return $ subQuery sql (Projection.width pj)
|
||||||
|
@ -34,7 +34,7 @@ import Database.Relational.Query.Internal.AggregatingContext (AggregatingContext
|
|||||||
import qualified Database.Relational.Query.Internal.AggregatingContext as Context
|
import qualified Database.Relational.Query.Internal.AggregatingContext as Context
|
||||||
|
|
||||||
import Database.Relational.Query.Monad.Class
|
import Database.Relational.Query.Monad.Class
|
||||||
(MonadQuery(..), MonadAggregate(..))
|
(MonadRestrict(..), MonadQuery(..), MonadAggregate(..))
|
||||||
|
|
||||||
|
|
||||||
-- | 'StateT' type to accumulate aggregating context.
|
-- | 'StateT' type to accumulate aggregating context.
|
||||||
@ -57,10 +57,13 @@ runAggregatingPrime = (`runAggregating` primeAggregatingContext)
|
|||||||
aggregate :: Monad m => m a -> Aggregatings m a
|
aggregate :: Monad m => m a -> Aggregatings m a
|
||||||
aggregate = lift
|
aggregate = lift
|
||||||
|
|
||||||
|
-- | Aggregated 'MonadRestrict'.
|
||||||
|
instance MonadRestrict m => MonadRestrict (Aggregatings m) where
|
||||||
|
restrictContext = aggregate . restrictContext
|
||||||
|
|
||||||
-- | Aggregated 'MonadQuery'.
|
-- | Aggregated 'MonadQuery'.
|
||||||
instance MonadQuery m => MonadQuery (Aggregatings m) where
|
instance MonadQuery m => MonadQuery (Aggregatings m) where
|
||||||
restrictJoin = aggregate . restrictJoin
|
restrictJoin = aggregate . restrictJoin
|
||||||
restrictQuery = aggregate . restrictQuery
|
|
||||||
unsafeSubQuery na = aggregate . unsafeSubQuery na
|
unsafeSubQuery na = aggregate . unsafeSubQuery na
|
||||||
|
|
||||||
-- | Unsafely update aggregating context.
|
-- | Unsafely update aggregating context.
|
||||||
|
@ -23,9 +23,8 @@ import Control.Monad.Trans.Class (MonadTrans (lift))
|
|||||||
import Control.Monad.Trans.State (modify, StateT, runStateT)
|
import Control.Monad.Trans.State (modify, StateT, runStateT)
|
||||||
import Control.Applicative (Applicative)
|
import Control.Applicative (Applicative)
|
||||||
|
|
||||||
import Database.Relational.Query.Internal.Context
|
import Database.Relational.Query.Monad.Trans.JoinState
|
||||||
(Context, primeContext, updateProduct)
|
(Context, primeContext, updateProduct, composeSQL)
|
||||||
import qualified Database.Relational.Query.Internal.Context as Context
|
|
||||||
import Database.Relational.Query.Internal.Product (NodeAttr, restrictProduct, growProduct)
|
import Database.Relational.Query.Internal.Product (NodeAttr, restrictProduct, growProduct)
|
||||||
import Database.Relational.Query.Projection (Projection)
|
import Database.Relational.Query.Projection (Projection)
|
||||||
import qualified Database.Relational.Query.Projection as Projection
|
import qualified Database.Relational.Query.Projection as Projection
|
||||||
@ -65,22 +64,17 @@ updateJoinRestriction e = updateContext (updateProduct d) where
|
|||||||
d Nothing = error "on: product is empty!"
|
d Nothing = error "on: product is empty!"
|
||||||
d (Just pt) = restrictProduct pt (fromTriBool e)
|
d (Just pt) = restrictProduct pt (fromTriBool e)
|
||||||
|
|
||||||
-- | Add whole query restriction.
|
|
||||||
updateRestriction :: Monad m => Expr Projection (Maybe Bool) -> QueryJoin m ()
|
|
||||||
updateRestriction e = updateContext (Context.addRestriction e)
|
|
||||||
|
|
||||||
{-
|
{-
|
||||||
takeProduct :: QueryJoin (Maybe QueryProductNode)
|
takeProduct :: QueryJoin (Maybe QueryProductNode)
|
||||||
takeProduct = queryCore Context.takeProduct
|
takeProduct = queryCore State.takeProduct
|
||||||
|
|
||||||
restoreLeft :: QueryProductNode -> NodeAttr -> QueryJoin ()
|
restoreLeft :: QueryProductNode -> NodeAttr -> QueryJoin ()
|
||||||
restoreLeft pL naR = updateContext $ Context.restoreLeft pL naR
|
restoreLeft pL naR = updateContext $ State.restoreLeft pL naR
|
||||||
-}
|
-}
|
||||||
|
|
||||||
-- | Basic query instance.
|
-- | Joinable query instance.
|
||||||
instance (Monad q, Functor q) => MonadQuery (QueryJoin q) where
|
instance (Monad q, Functor q) => MonadQuery (QueryJoin q) where
|
||||||
restrictJoin = updateJoinRestriction
|
restrictJoin = updateJoinRestriction
|
||||||
restrictQuery = updateRestriction
|
|
||||||
unsafeSubQuery = unsafeSubQueryWithAttr
|
unsafeSubQuery = unsafeSubQueryWithAttr
|
||||||
-- unsafeMergeAnotherQuery = unsafeQueryMergeWithAttr
|
-- unsafeMergeAnotherQuery = unsafeQueryMergeWithAttr
|
||||||
|
|
||||||
@ -106,7 +100,7 @@ unsafeQueryMergeWithAttr = unsafeMergeAnother
|
|||||||
-}
|
-}
|
||||||
|
|
||||||
-- | Run 'QueryJoin' to get SQL string.
|
-- | Run 'QueryJoin' to get SQL string.
|
||||||
expandSQL :: Monad m => QueryJoin m (Projection r, t) -> m ((String, Projection r), t)
|
expandSQL :: Monad m => QueryJoin m (Projection r, st) -> m ((String, Projection r), st)
|
||||||
expandSQL qp = do
|
expandSQL qp = do
|
||||||
((pj, st), c) <- runQueryPrime qp
|
((pj, st), c) <- runQueryPrime qp
|
||||||
return ((Context.composeSQL pj c, pj), st)
|
return ((composeSQL pj c, pj), st)
|
||||||
|
@ -1,7 +1,7 @@
|
|||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
|
||||||
-- |
|
-- |
|
||||||
-- Module : Database.Relational.Query.Internal.Context
|
-- Module : Database.Relational.Query.Monad.Trans.JoinState
|
||||||
-- Copyright : 2013 Kei Hibino
|
-- Copyright : 2013 Kei Hibino
|
||||||
-- License : BSD3
|
-- License : BSD3
|
||||||
--
|
--
|
||||||
@ -9,25 +9,21 @@
|
|||||||
-- Stability : experimental
|
-- Stability : experimental
|
||||||
-- Portability : unknown
|
-- Portability : unknown
|
||||||
--
|
--
|
||||||
-- This module provides context definition for
|
-- This module provides state definition for
|
||||||
-- "Database.Relational.Query.Monad.Trans.Join" and
|
-- "Database.Relational.Query.Monad.Trans.Join".
|
||||||
-- "Database.Relational.Query.Monad.Trans.Ordering".
|
module Database.Relational.Query.Monad.Trans.JoinState (
|
||||||
module Database.Relational.Query.Internal.Context (
|
|
||||||
-- * Join context
|
-- * Join context
|
||||||
Context,
|
Context,
|
||||||
|
|
||||||
primeContext,
|
primeContext,
|
||||||
|
|
||||||
updateProduct, -- takeProduct, restoreLeft,
|
updateProduct, -- takeProduct, restoreLeft,
|
||||||
addRestriction,
|
|
||||||
|
|
||||||
composeSQL
|
composeSQL
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Prelude hiding (product)
|
import Prelude hiding (product)
|
||||||
|
|
||||||
import Database.Relational.Query.Expr (Expr, fromTriBool, exprAnd)
|
|
||||||
import Database.Relational.Query.Expr.Unsafe (showExpr)
|
|
||||||
import Database.Relational.Query.Sub (asColumnN)
|
import Database.Relational.Query.Sub (asColumnN)
|
||||||
|
|
||||||
import Database.Relational.Query.Internal.Product (QueryProductNode, QueryProduct, queryProductSQL)
|
import Database.Relational.Query.Internal.Product (QueryProductNode, QueryProduct, queryProductSQL)
|
||||||
@ -42,13 +38,11 @@ import qualified Language.SQL.Keyword as SQL
|
|||||||
|
|
||||||
-- | Context type for QueryJoin.
|
-- | Context type for QueryJoin.
|
||||||
data Context = Context
|
data Context = Context
|
||||||
{ product :: Maybe QueryProductNode
|
{ product :: Maybe QueryProductNode }
|
||||||
, restriction :: Maybe (Expr Projection Bool)
|
|
||||||
}
|
|
||||||
|
|
||||||
-- | Initial 'Context'.
|
-- | Initial 'Context'.
|
||||||
primeContext :: Context
|
primeContext :: Context
|
||||||
primeContext = Context Nothing Nothing
|
primeContext = Context Nothing
|
||||||
|
|
||||||
-- | Update product of 'Context'.
|
-- | Update product of 'Context'.
|
||||||
updateProduct' :: (Maybe QueryProductNode -> Maybe QueryProductNode) -> Context -> Context
|
updateProduct' :: (Maybe QueryProductNode -> Maybe QueryProductNode) -> Context -> Context
|
||||||
@ -64,28 +58,19 @@ updateProduct uf = updateProduct' (Just . uf)
|
|||||||
-- restoreLeft :: QueryProductNode -> Product.NodeAttr -> Context -> Context
|
-- restoreLeft :: QueryProductNode -> Product.NodeAttr -> Context -> Context
|
||||||
-- restoreLeft pL naR ctx = updateProduct (Product.growLeft pL naR) ctx
|
-- restoreLeft pL naR ctx = updateProduct (Product.growLeft pL naR) ctx
|
||||||
|
|
||||||
-- | Add restriction of 'Context'.
|
|
||||||
addRestriction :: Expr Projection (Maybe Bool) -> Context -> Context
|
|
||||||
addRestriction e1 ctx =
|
|
||||||
ctx { restriction = Just . uf . restriction $ ctx }
|
|
||||||
where uf Nothing = fromTriBool e1
|
|
||||||
uf (Just e0) = e0 `exprAnd` fromTriBool e1
|
|
||||||
|
|
||||||
-- | Compose SQL String from QueryJoin monad object.
|
-- | Compose SQL String from QueryJoin monad object.
|
||||||
composeSQL' :: Projection r -> QueryProduct -> Maybe (Expr Projection Bool) -> String
|
composeSQL' :: Projection r -> QueryProduct -> String
|
||||||
composeSQL' pj pd re =
|
composeSQL' pj pd =
|
||||||
unwordsSQL
|
unwordsSQL
|
||||||
$ [SELECT, columns' `SQL.sepBy` ", ",
|
$ [SELECT, columns' `SQL.sepBy` ", ",
|
||||||
FROM, SQL.word . queryProductSQL $ pd]
|
FROM, SQL.word . queryProductSQL $ pd]
|
||||||
++ wheres re
|
where columns' = zipWith
|
||||||
where columns' = zipWith
|
(\f n -> SQL.word f `asColumnN` n)
|
||||||
(\f n -> SQL.word f `asColumnN` n)
|
(Projection.columns pj)
|
||||||
(Projection.columns pj)
|
[(0 :: Int)..]
|
||||||
[(0 :: Int)..]
|
|
||||||
wheres = Prelude.maybe [] (\e -> [WHERE, SQL.word . showExpr $ e])
|
|
||||||
|
|
||||||
-- | Compose SQL String from QueryJoin monad object.
|
-- | Compose SQL String from QueryJoin monad object.
|
||||||
composeSQL :: Projection r -> Context -> String
|
composeSQL :: Projection r -> Context -> String
|
||||||
composeSQL pj c = composeSQL' pj
|
composeSQL pj c = composeSQL' pj
|
||||||
(maybe (error "relation: empty product!") (Product.nodeTree) (product c))
|
(maybe (error "relation: empty product!") (Product.nodeTree) (product c))
|
||||||
(restriction c)
|
|
@ -19,8 +19,9 @@ module Database.Relational.Query.Monad.Trans.Ordering (
|
|||||||
-- * API of query with ordering
|
-- * API of query with ordering
|
||||||
asc, desc,
|
asc, desc,
|
||||||
|
|
||||||
-- * Result order by SQLs
|
-- * Result SQL order-by clause
|
||||||
appendOrderBys
|
appendOrderBys,
|
||||||
|
OrderByAppend (orderByAppend)
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Control.Monad.Trans.Class (MonadTrans (lift))
|
import Control.Monad.Trans.Class (MonadTrans (lift))
|
||||||
@ -38,7 +39,7 @@ import Database.Relational.Query.Aggregation (Aggregation)
|
|||||||
import qualified Database.Relational.Query.Aggregation as Aggregation
|
import qualified Database.Relational.Query.Aggregation as Aggregation
|
||||||
|
|
||||||
import Database.Relational.Query.Monad.Class
|
import Database.Relational.Query.Monad.Class
|
||||||
(MonadQuery(..), MonadAggregate(..))
|
(MonadRestrict(..), MonadQuery(..), MonadAggregate(..))
|
||||||
|
|
||||||
|
|
||||||
-- | 'StateT' type to accumulate ordering context.
|
-- | 'StateT' type to accumulate ordering context.
|
||||||
@ -62,10 +63,13 @@ runOrderingsPrime q = runOrderings q $ primeOrderingContext
|
|||||||
orderings :: Monad m => m a -> Orderings p m a
|
orderings :: Monad m => m a -> Orderings p m a
|
||||||
orderings = lift
|
orderings = lift
|
||||||
|
|
||||||
|
-- | 'MonadRestrict' with ordering.
|
||||||
|
instance MonadRestrict m => MonadRestrict (Orderings p m) where
|
||||||
|
restrictContext = orderings . restrictContext
|
||||||
|
|
||||||
-- | 'MonadQuery' with ordering.
|
-- | 'MonadQuery' with ordering.
|
||||||
instance MonadQuery m => MonadQuery (Orderings p m) where
|
instance MonadQuery m => MonadQuery (Orderings p m) where
|
||||||
restrictJoin = orderings . restrictJoin
|
restrictJoin = orderings . restrictJoin
|
||||||
restrictQuery = orderings . restrictQuery
|
|
||||||
unsafeSubQuery na = orderings . unsafeSubQuery na
|
unsafeSubQuery na = orderings . unsafeSubQuery na
|
||||||
-- unsafeMergeAnotherQuery = unsafeMergeAnotherOrderBys
|
-- unsafeMergeAnotherQuery = unsafeMergeAnotherOrderBys
|
||||||
|
|
||||||
@ -140,8 +144,10 @@ appendOrderBys' c = (++ d (Context.composeOrderBys c)) where
|
|||||||
d "" = ""
|
d "" = ""
|
||||||
d s = ' ' : s
|
d s = ' ' : s
|
||||||
|
|
||||||
|
newtype OrderByAppend = OrderByAppend { orderByAppend :: String -> String }
|
||||||
|
|
||||||
-- | Run 'Orderings' to get query result and order-by appending function.
|
-- | Run 'Orderings' to get query result and order-by appending function.
|
||||||
appendOrderBys :: MonadQuery m
|
appendOrderBys :: (Monad m, Functor m)
|
||||||
=> Orderings p m a -- ^ 'Orderings' to run
|
=> Orderings p m a -- ^ 'Orderings' to run
|
||||||
-> m (a, String -> String) -- ^ Query result and order-by appending function.
|
-> m (a, OrderByAppend) -- ^ Query result and order-by appending function.
|
||||||
appendOrderBys q = second appendOrderBys' <$> runOrderingsPrime q
|
appendOrderBys q = second (OrderByAppend . appendOrderBys') <$> runOrderingsPrime q
|
||||||
|
@ -0,0 +1,90 @@
|
|||||||
|
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||||
|
|
||||||
|
-- |
|
||||||
|
-- Module : Database.Relational.Query.Monad.Trans.Restrict
|
||||||
|
-- Copyright : 2013 Kei Hibino
|
||||||
|
-- License : BSD3
|
||||||
|
--
|
||||||
|
-- Maintainer : ex8k.hibino@gmail.com
|
||||||
|
-- Stability : experimental
|
||||||
|
-- Portability : unknown
|
||||||
|
--
|
||||||
|
-- This module defines monad transformer which lift to basic 'MonadQuery'.
|
||||||
|
module Database.Relational.Query.Monad.Trans.Restrict (
|
||||||
|
-- * Transformer into restricted context
|
||||||
|
Restrict, restrict,
|
||||||
|
|
||||||
|
-- * Result SQL wheres clause
|
||||||
|
appendWheres,
|
||||||
|
WheresAppend (wheresAppend)
|
||||||
|
) where
|
||||||
|
|
||||||
|
import Control.Monad.Trans.Class (MonadTrans (lift))
|
||||||
|
import Control.Monad.Trans.State (modify, StateT, runStateT)
|
||||||
|
import Control.Applicative (Applicative, (<$>))
|
||||||
|
import Control.Arrow (second)
|
||||||
|
|
||||||
|
import Database.Relational.Query.Internal.RestrictContext
|
||||||
|
(RestrictContext, primeRestrictContext, addRestriction)
|
||||||
|
import qualified Database.Relational.Query.Internal.RestrictContext as RestrictContext
|
||||||
|
import Database.Relational.Query.Projection (Projection)
|
||||||
|
import Database.Relational.Query.Expr (Expr)
|
||||||
|
|
||||||
|
import Database.Relational.Query.Monad.Class (MonadRestrict(..), MonadQuery (..))
|
||||||
|
|
||||||
|
|
||||||
|
-- | 'StateT' type to accumulate join product context.
|
||||||
|
newtype Restrict m a =
|
||||||
|
Restrict { queryState :: StateT RestrictContext m a }
|
||||||
|
deriving (MonadTrans, Monad, Functor, Applicative)
|
||||||
|
|
||||||
|
-- | Run 'Restrict' to expand context state.
|
||||||
|
runRestrict :: Restrict m a -- ^ RestrictContext to expand
|
||||||
|
-> RestrictContext -- ^ Initial context
|
||||||
|
-> m (a, RestrictContext) -- ^ Expanded result
|
||||||
|
runRestrict = runStateT . queryState
|
||||||
|
|
||||||
|
-- | Run 'Restrict' with primary empty context to expand context state.
|
||||||
|
runRestrictPrime :: Restrict m a -- ^ RestrictContext to expand
|
||||||
|
-> m (a, RestrictContext) -- ^ Expanded result
|
||||||
|
runRestrictPrime q = runRestrict q primeRestrictContext
|
||||||
|
|
||||||
|
-- | Lift to 'Restrict'
|
||||||
|
restrict :: Monad m => m a -> Restrict m a
|
||||||
|
restrict = lift
|
||||||
|
|
||||||
|
-- | Unsafely update join product context.
|
||||||
|
updateRestrictContext :: Monad m => (RestrictContext -> RestrictContext) -> Restrict m ()
|
||||||
|
updateRestrictContext = Restrict . modify
|
||||||
|
|
||||||
|
-- | Add whole query restriction.
|
||||||
|
updateRestriction :: Monad m => Expr Projection (Maybe Bool) -> Restrict m ()
|
||||||
|
updateRestriction e = updateRestrictContext (addRestriction e)
|
||||||
|
|
||||||
|
-- | 'MonadRestrict' instance.
|
||||||
|
instance (Monad q, Functor q) => MonadRestrict (Restrict q) where
|
||||||
|
restrictContext = updateRestriction
|
||||||
|
|
||||||
|
-- | Restricted 'MonadQuery' instance.
|
||||||
|
instance MonadQuery q => MonadQuery (Restrict q) where
|
||||||
|
restrictJoin = restrict . restrictJoin
|
||||||
|
unsafeSubQuery a = restrict . unsafeSubQuery a
|
||||||
|
|
||||||
|
-- | Get order-by appending function from 'RestrictContext'.
|
||||||
|
appendWheres' :: RestrictContext -> String -> String
|
||||||
|
appendWheres' c = (++ d (RestrictContext.composeWheres c)) where
|
||||||
|
d "" = ""
|
||||||
|
d s = ' ' : s
|
||||||
|
|
||||||
|
newtype WheresAppend = WheresAppend { wheresAppend :: String -> String }
|
||||||
|
|
||||||
|
-- | Run 'Restricts' to get query result and order-by appending function.
|
||||||
|
appendWheres :: (Monad m, Functor m)
|
||||||
|
=> Restrict m a -- ^ 'Restrict' to run
|
||||||
|
-> m (a, WheresAppend) -- ^ Query result and order-by appending function.
|
||||||
|
appendWheres r = second (WheresAppend . appendWheres') <$> runRestrictPrime r
|
||||||
|
|
||||||
|
-- expandSQL :: Monad m => Restrict m a -> m (String, a)
|
||||||
|
-- expandSQL r = do
|
||||||
|
-- (a, c) <- runRestrictPrime r
|
||||||
|
-- return (RestrictContext.composeSQL c, a)
|
Loading…
Reference in New Issue
Block a user