{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
module ProjectM36.StaticOptimizer where
import ProjectM36.Base
import ProjectM36.GraphRefRelationalExpr
import ProjectM36.Relation
import ProjectM36.RelationalExpression
import ProjectM36.TransGraphRelationalExpression as TGRE hiding (askGraph)
import ProjectM36.Error
import ProjectM36.Transaction
import ProjectM36.NormalizeExpr
import qualified ProjectM36.Attribute as A
import qualified ProjectM36.AttributeNames as AS
import ProjectM36.TupleSet
#if MIN_VERSION_base(4,18,0)
import Control.Monad (foldM)
#endif
import Control.Monad.State
import Control.Monad.Reader
import Control.Monad.Except
import Control.Monad.Trans.Except
import Data.Functor.Identity
import Data.List.NonEmpty (NonEmpty(..))
import qualified Data.List.NonEmpty as NE
import qualified Data.Map as M
import qualified Data.Set as S
import Data.Functor.Foldable as Fold
data GraphRefSOptRelationalExprEnv =
GraphRefSOptRelationalExprEnv
{
GraphRefSOptRelationalExprEnv -> TransactionGraph
ore_graph :: TransactionGraph,
GraphRefSOptRelationalExprEnv -> Maybe DatabaseContext
ore_mcontext :: Maybe DatabaseContext
}
type GraphRefSOptRelationalExprM a = ReaderT GraphRefSOptRelationalExprEnv (ExceptT RelationalError Identity) a
data GraphRefSOptDatabaseContextExprEnv =
GraphRefSOptDatabaseContextExprEnv
{
GraphRefSOptDatabaseContextExprEnv -> TransactionGraph
odce_graph :: TransactionGraph,
GraphRefSOptDatabaseContextExprEnv -> DatabaseContext
odce_context :: DatabaseContext,
GraphRefSOptDatabaseContextExprEnv -> TransactionId
odce_transId :: TransactionId
}
type GraphRefSOptDatabaseContextExprM a = ReaderT GraphRefSOptDatabaseContextExprEnv (ExceptT RelationalError Identity) a
optimizeAndEvalRelationalExpr :: RelationalExprEnv -> RelationalExpr -> Either RelationalError Relation
optimizeAndEvalRelationalExpr :: RelationalExprEnv
-> RelationalExpr -> Either RelationalError Relation
optimizeAndEvalRelationalExpr RelationalExprEnv
env RelationalExpr
expr = do
let graph :: TransactionGraph
graph = RelationalExprEnv -> TransactionGraph
re_graph RelationalExprEnv
env
ctx :: DatabaseContext
ctx = RelationalExprEnv -> DatabaseContext
re_context RelationalExprEnv
env
gfEnv :: GraphRefRelationalExprEnv
gfEnv = Maybe DatabaseContext
-> TransactionGraph -> GraphRefRelationalExprEnv
freshGraphRefRelationalExprEnv (forall a. a -> Maybe a
Just DatabaseContext
ctx) TransactionGraph
graph
GraphRefRelationalExpr
optExpr <- RelationalExprEnv
-> RelationalExpr -> Either RelationalError GraphRefRelationalExpr
optimizeRelationalExpr RelationalExprEnv
env RelationalExpr
expr
forall a.
GraphRefRelationalExprEnv
-> GraphRefRelationalExprM a -> Either RelationalError a
runGraphRefRelationalExprM GraphRefRelationalExprEnv
gfEnv (GraphRefRelationalExpr -> GraphRefRelationalExprM Relation
evalGraphRefRelationalExpr GraphRefRelationalExpr
optExpr)
optimizeRelationalExpr :: RelationalExprEnv -> RelationalExpr -> Either RelationalError GraphRefRelationalExpr
optimizeRelationalExpr :: RelationalExprEnv
-> RelationalExpr -> Either RelationalError GraphRefRelationalExpr
optimizeRelationalExpr RelationalExprEnv
env RelationalExpr
expr = do
let gfExpr :: GraphRefRelationalExpr
gfExpr = forall a. GraphRefTransactionMarker -> ProcessExprM a -> a
runProcessExprM GraphRefTransactionMarker
UncommittedContextMarker (RelationalExpr -> ProcessExprM GraphRefRelationalExpr
processRelationalExpr RelationalExpr
expr)
ctx :: DatabaseContext
ctx = RelationalExprEnv -> DatabaseContext
re_context RelationalExprEnv
env
forall a.
Maybe DatabaseContext
-> TransactionGraph
-> GraphRefSOptRelationalExprM a
-> Either RelationalError a
runGraphRefSOptRelationalExprM (forall a. a -> Maybe a
Just DatabaseContext
ctx) (RelationalExprEnv -> TransactionGraph
re_graph RelationalExprEnv
env) (GraphRefRelationalExpr
-> GraphRefSOptRelationalExprM GraphRefRelationalExpr
fullOptimizeGraphRefRelationalExpr GraphRefRelationalExpr
gfExpr)
class Monad m => AskGraphContext m where
askGraph :: m TransactionGraph
askContext :: m DatabaseContext
instance AskGraphContext (ReaderT GraphRefSOptDatabaseContextExprEnv (ExceptT RelationalError Identity)) where
askGraph :: ReaderT
GraphRefSOptDatabaseContextExprEnv
(ExceptT RelationalError Identity)
TransactionGraph
askGraph = forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks GraphRefSOptDatabaseContextExprEnv -> TransactionGraph
odce_graph
askContext :: ReaderT
GraphRefSOptDatabaseContextExprEnv
(ExceptT RelationalError Identity)
DatabaseContext
askContext = forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks GraphRefSOptDatabaseContextExprEnv -> DatabaseContext
odce_context
instance AskGraphContext (ReaderT GraphRefSOptRelationalExprEnv (ExceptT RelationalError Identity)) where
askGraph :: ReaderT
GraphRefSOptRelationalExprEnv
(ExceptT RelationalError Identity)
TransactionGraph
askGraph = forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks GraphRefSOptRelationalExprEnv -> TransactionGraph
ore_graph
askContext :: ReaderT
GraphRefSOptRelationalExprEnv
(ExceptT RelationalError Identity)
DatabaseContext
askContext = do
Maybe DatabaseContext
mctx <- forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks GraphRefSOptRelationalExprEnv -> Maybe DatabaseContext
ore_mcontext
case Maybe DatabaseContext
mctx of
Maybe DatabaseContext
Nothing -> forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError RelationalError
NoUncommittedContextInEvalError
Just DatabaseContext
ctx -> forall (f :: * -> *) a. Applicative f => a -> f a
pure DatabaseContext
ctx
askTransId :: GraphRefSOptDatabaseContextExprM TransactionId
askTransId :: GraphRefSOptDatabaseContextExprM TransactionId
askTransId = forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks GraphRefSOptDatabaseContextExprEnv -> TransactionId
odce_transId
askMaybeContext :: GraphRefSOptRelationalExprM (Maybe DatabaseContext)
askMaybeContext :: GraphRefSOptRelationalExprM (Maybe DatabaseContext)
askMaybeContext = forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks GraphRefSOptRelationalExprEnv -> Maybe DatabaseContext
ore_mcontext
optimizeDatabaseContextExpr :: DatabaseContextExpr -> GraphRefSOptDatabaseContextExprM GraphRefDatabaseContextExpr
optimizeDatabaseContextExpr :: DatabaseContextExpr
-> GraphRefSOptDatabaseContextExprM GraphRefDatabaseContextExpr
optimizeDatabaseContextExpr DatabaseContextExpr
expr = do
let gfExpr :: GraphRefDatabaseContextExpr
gfExpr = forall a. GraphRefTransactionMarker -> ProcessExprM a -> a
runProcessExprM GraphRefTransactionMarker
UncommittedContextMarker (DatabaseContextExpr -> ProcessExprM GraphRefDatabaseContextExpr
processDatabaseContextExpr DatabaseContextExpr
expr)
GraphRefDatabaseContextExpr
-> GraphRefSOptDatabaseContextExprM GraphRefDatabaseContextExpr
optimizeGraphRefDatabaseContextExpr GraphRefDatabaseContextExpr
gfExpr
optimizeAndEvalDatabaseContextExpr :: Bool -> DatabaseContextExpr -> DatabaseContextEvalMonad ()
optimizeAndEvalDatabaseContextExpr :: Bool -> DatabaseContextExpr -> DatabaseContextEvalMonad ()
optimizeAndEvalDatabaseContextExpr Bool
optimize DatabaseContextExpr
expr = do
TransactionGraph
graph <- forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks DatabaseContextEvalEnv -> TransactionGraph
dce_graph
TransactionId
transId <- forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks DatabaseContextEvalEnv -> TransactionId
dce_transId
DatabaseContext
context <- DatabaseContextEvalMonad DatabaseContext
getStateContext
let gfExpr :: GraphRefDatabaseContextExpr
gfExpr = forall a. GraphRefTransactionMarker -> ProcessExprM a -> a
runProcessExprM GraphRefTransactionMarker
UncommittedContextMarker (DatabaseContextExpr -> ProcessExprM GraphRefDatabaseContextExpr
processDatabaseContextExpr DatabaseContextExpr
expr)
eOptExpr :: Either RelationalError GraphRefDatabaseContextExpr
eOptExpr = if Bool
optimize then
forall a.
TransactionId
-> DatabaseContext
-> TransactionGraph
-> GraphRefSOptDatabaseContextExprM a
-> Either RelationalError a
runGraphRefSOptDatabaseContextExprM TransactionId
transId DatabaseContext
context TransactionGraph
graph (GraphRefDatabaseContextExpr
-> GraphRefSOptDatabaseContextExprM GraphRefDatabaseContextExpr
optimizeGraphRefDatabaseContextExpr GraphRefDatabaseContextExpr
gfExpr)
else
forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefDatabaseContextExpr
gfExpr
case Either RelationalError GraphRefDatabaseContextExpr
eOptExpr of
Left RelationalError
err -> forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError RelationalError
err
Right GraphRefDatabaseContextExpr
optExpr -> GraphRefDatabaseContextExpr -> DatabaseContextEvalMonad ()
evalGraphRefDatabaseContextExpr GraphRefDatabaseContextExpr
optExpr
optimizeAndEvalTransGraphRelationalExpr :: TransactionGraph -> TransGraphRelationalExpr -> Either RelationalError Relation
optimizeAndEvalTransGraphRelationalExpr :: TransactionGraph
-> TransGraphRelationalExpr -> Either RelationalError Relation
optimizeAndEvalTransGraphRelationalExpr TransactionGraph
graph TransGraphRelationalExpr
tgExpr = do
GraphRefRelationalExpr
gfExpr <- TransGraphEvalEnv
-> TransGraphRelationalExpr
-> Either RelationalError GraphRefRelationalExpr
TGRE.process (TransactionGraph -> TransGraphEvalEnv
TransGraphEvalEnv TransactionGraph
graph) TransGraphRelationalExpr
tgExpr
GraphRefRelationalExpr
optExpr <- forall a.
Maybe DatabaseContext
-> TransactionGraph
-> GraphRefSOptRelationalExprM a
-> Either RelationalError a
runGraphRefSOptRelationalExprM forall a. Maybe a
Nothing TransactionGraph
graph (GraphRefRelationalExpr
-> GraphRefSOptRelationalExprM GraphRefRelationalExpr
fullOptimizeGraphRefRelationalExpr GraphRefRelationalExpr
gfExpr)
let gfEnv :: GraphRefRelationalExprEnv
gfEnv = Maybe DatabaseContext
-> TransactionGraph -> GraphRefRelationalExprEnv
freshGraphRefRelationalExprEnv forall a. Maybe a
Nothing TransactionGraph
graph
forall a.
GraphRefRelationalExprEnv
-> GraphRefRelationalExprM a -> Either RelationalError a
runGraphRefRelationalExprM GraphRefRelationalExprEnv
gfEnv (GraphRefRelationalExpr -> GraphRefRelationalExprM Relation
evalGraphRefRelationalExpr GraphRefRelationalExpr
optExpr)
optimizeAndEvalDatabaseContextIOExpr :: DatabaseContextIOExpr -> DatabaseContextIOEvalMonad (Either RelationalError ())
optimizeAndEvalDatabaseContextIOExpr :: DatabaseContextIOExpr
-> DatabaseContextIOEvalMonad (Either RelationalError ())
optimizeAndEvalDatabaseContextIOExpr DatabaseContextIOExpr
expr = do
TransactionId
transId <- forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks DatabaseContextIOEvalEnv -> TransactionId
dbcio_transId
DatabaseContext
ctx <- DatabaseContextIOEvalMonad DatabaseContext
getDBCIOContext
TransactionGraph
graph <- forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks DatabaseContextIOEvalEnv -> TransactionGraph
dbcio_graph
let gfExpr :: GraphRefDatabaseContextIOExpr
gfExpr = forall a. GraphRefTransactionMarker -> ProcessExprM a -> a
runProcessExprM GraphRefTransactionMarker
UncommittedContextMarker (DatabaseContextIOExpr -> ProcessExprM GraphRefDatabaseContextIOExpr
processDatabaseContextIOExpr DatabaseContextIOExpr
expr)
eOptExpr :: Either RelationalError GraphRefDatabaseContextIOExpr
eOptExpr = forall a.
TransactionId
-> DatabaseContext
-> TransactionGraph
-> GraphRefSOptDatabaseContextExprM a
-> Either RelationalError a
runGraphRefSOptDatabaseContextExprM TransactionId
transId DatabaseContext
ctx TransactionGraph
graph (GraphRefDatabaseContextIOExpr
-> GraphRefSOptDatabaseContextExprM GraphRefDatabaseContextIOExpr
optimizeDatabaseContextIOExpr GraphRefDatabaseContextIOExpr
gfExpr)
case Either RelationalError GraphRefDatabaseContextIOExpr
eOptExpr of
Left RelationalError
err -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a b. a -> Either a b
Left RelationalError
err)
Right GraphRefDatabaseContextIOExpr
optExpr ->
GraphRefDatabaseContextIOExpr
-> DatabaseContextIOEvalMonad (Either RelationalError ())
evalGraphRefDatabaseContextIOExpr GraphRefDatabaseContextIOExpr
optExpr
runGraphRefSOptRelationalExprM ::
Maybe DatabaseContext ->
TransactionGraph ->
GraphRefSOptRelationalExprM a ->
Either RelationalError a
runGraphRefSOptRelationalExprM :: forall a.
Maybe DatabaseContext
-> TransactionGraph
-> GraphRefSOptRelationalExprM a
-> Either RelationalError a
runGraphRefSOptRelationalExprM Maybe DatabaseContext
mctx TransactionGraph
graph GraphRefSOptRelationalExprM a
m = forall a. Identity a -> a
runIdentity (forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT GraphRefSOptRelationalExprM a
m GraphRefSOptRelationalExprEnv
env))
where
env :: GraphRefSOptRelationalExprEnv
env = GraphRefSOptRelationalExprEnv {
ore_graph :: TransactionGraph
ore_graph = TransactionGraph
graph,
ore_mcontext :: Maybe DatabaseContext
ore_mcontext = Maybe DatabaseContext
mctx
}
runGraphRefSOptDatabaseContextExprM ::
TransactionId ->
DatabaseContext ->
TransactionGraph ->
GraphRefSOptDatabaseContextExprM a ->
Either RelationalError a
runGraphRefSOptDatabaseContextExprM :: forall a.
TransactionId
-> DatabaseContext
-> TransactionGraph
-> GraphRefSOptDatabaseContextExprM a
-> Either RelationalError a
runGraphRefSOptDatabaseContextExprM TransactionId
tid DatabaseContext
ctx TransactionGraph
graph GraphRefSOptDatabaseContextExprM a
m =
forall a. Identity a -> a
runIdentity (forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT GraphRefSOptDatabaseContextExprM a
m GraphRefSOptDatabaseContextExprEnv
env))
where
env :: GraphRefSOptDatabaseContextExprEnv
env = GraphRefSOptDatabaseContextExprEnv {
odce_graph :: TransactionGraph
odce_graph = TransactionGraph
graph,
odce_context :: DatabaseContext
odce_context = DatabaseContext
ctx,
odce_transId :: TransactionId
odce_transId = TransactionId
tid
}
optimizeGraphRefRelationalExpr' ::
Maybe DatabaseContext ->
TransactionGraph ->
GraphRefRelationalExpr ->
Either RelationalError GraphRefRelationalExpr
optimizeGraphRefRelationalExpr' :: Maybe DatabaseContext
-> TransactionGraph
-> GraphRefRelationalExpr
-> Either RelationalError GraphRefRelationalExpr
optimizeGraphRefRelationalExpr' Maybe DatabaseContext
mctx TransactionGraph
graph GraphRefRelationalExpr
expr =
forall a. Identity a -> a
runIdentity (forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT (GraphRefRelationalExpr
-> GraphRefSOptRelationalExprM GraphRefRelationalExpr
optimizeGraphRefRelationalExpr GraphRefRelationalExpr
expr) GraphRefSOptRelationalExprEnv
env))
where
env :: GraphRefSOptRelationalExprEnv
env = GraphRefSOptRelationalExprEnv {
ore_graph :: TransactionGraph
ore_graph = TransactionGraph
graph,
ore_mcontext :: Maybe DatabaseContext
ore_mcontext = Maybe DatabaseContext
mctx
}
liftGraphRefRelExpr :: GraphRefSOptRelationalExprM a -> GraphRefSOptDatabaseContextExprM a
liftGraphRefRelExpr :: forall a.
GraphRefSOptRelationalExprM a -> GraphRefSOptDatabaseContextExprM a
liftGraphRefRelExpr GraphRefSOptRelationalExprM a
m = do
DatabaseContext
context <- forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks GraphRefSOptDatabaseContextExprEnv -> DatabaseContext
odce_context
TransactionGraph
graph <- forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks GraphRefSOptDatabaseContextExprEnv -> TransactionGraph
odce_graph
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) e a. Monad m => Either e a -> ExceptT e m a
except forall a b. (a -> b) -> a -> b
$ forall a.
Maybe DatabaseContext
-> TransactionGraph
-> GraphRefSOptRelationalExprM a
-> Either RelationalError a
runGraphRefSOptRelationalExprM (forall a. a -> Maybe a
Just DatabaseContext
context) TransactionGraph
graph GraphRefSOptRelationalExprM a
m
fullOptimizeGraphRefRelationalExpr :: GraphRefRelationalExpr -> GraphRefSOptRelationalExprM GraphRefRelationalExpr
fullOptimizeGraphRefRelationalExpr :: GraphRefRelationalExpr
-> GraphRefSOptRelationalExprM GraphRefRelationalExpr
fullOptimizeGraphRefRelationalExpr GraphRefRelationalExpr
expr = do
GraphRefRelationalExpr
optExpr <- GraphRefRelationalExpr
-> GraphRefSOptRelationalExprM GraphRefRelationalExpr
optimizeGraphRefRelationalExpr GraphRefRelationalExpr
expr
let optExpr' :: GraphRefRelationalExpr
optExpr' = GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionPushdown (GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionCollapse GraphRefRelationalExpr
optExpr)
GraphRefRelationalExpr
-> GraphRefSOptRelationalExprM GraphRefRelationalExpr
applyStaticJoinElimination GraphRefRelationalExpr
optExpr'
optimizeGraphRefRelationalExpr :: GraphRefRelationalExpr -> GraphRefSOptRelationalExprM GraphRefRelationalExpr
optimizeGraphRefRelationalExpr :: GraphRefRelationalExpr
-> GraphRefSOptRelationalExprM GraphRefRelationalExpr
optimizeGraphRefRelationalExpr e :: GraphRefRelationalExpr
e@(MakeStaticRelation Attributes
_ RelationTupleSet
_) = forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefRelationalExpr
e
optimizeGraphRefRelationalExpr e :: GraphRefRelationalExpr
e@MakeRelationFromExprs{} = forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefRelationalExpr
e
optimizeGraphRefRelationalExpr e :: GraphRefRelationalExpr
e@(ExistingRelation Relation
_) = forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefRelationalExpr
e
optimizeGraphRefRelationalExpr e :: GraphRefRelationalExpr
e@(RelationValuedAttribute{}) = forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefRelationalExpr
e
optimizeGraphRefRelationalExpr e :: GraphRefRelationalExpr
e@(RelationVariable AttributeName
_ GraphRefTransactionMarker
_) = forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefRelationalExpr
e
optimizeGraphRefRelationalExpr (Project AttributeNamesBase GraphRefTransactionMarker
attrNameSet GraphRefRelationalExpr
expr) = do
TransactionGraph
graph <- forall (m :: * -> *). AskGraphContext m => m TransactionGraph
askGraph
Maybe DatabaseContext
mctx <- GraphRefSOptRelationalExprM (Maybe DatabaseContext)
askMaybeContext
let relType :: Either RelationalError Relation
relType = forall a.
GraphRefRelationalExprEnv
-> GraphRefRelationalExprM a -> Either RelationalError a
runGraphRefRelationalExprM GraphRefRelationalExprEnv
gfEnv (GraphRefRelationalExpr -> GraphRefRelationalExprM Relation
typeForGraphRefRelationalExpr GraphRefRelationalExpr
expr)
gfEnv :: GraphRefRelationalExprEnv
gfEnv = Maybe DatabaseContext
-> TransactionGraph -> GraphRefRelationalExprEnv
freshGraphRefRelationalExprEnv Maybe DatabaseContext
mctx TransactionGraph
graph
case Either RelationalError Relation
relType of
Left RelationalError
err -> forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError RelationalError
err
Right Relation
relType2
| forall a. AttributeNamesBase a
AS.all forall a. Eq a => a -> a -> Bool
== AttributeNamesBase GraphRefTransactionMarker
attrNameSet ->
GraphRefRelationalExpr
-> GraphRefSOptRelationalExprM GraphRefRelationalExpr
optimizeGraphRefRelationalExpr GraphRefRelationalExpr
expr
| forall a. Set AttributeName -> AttributeNamesBase a
AttributeNames (Relation -> Set AttributeName
attributeNames Relation
relType2) forall a. Eq a => a -> a -> Bool
== AttributeNamesBase GraphRefTransactionMarker
attrNameSet ->
GraphRefRelationalExpr
-> GraphRefSOptRelationalExprM GraphRefRelationalExpr
optimizeGraphRefRelationalExpr GraphRefRelationalExpr
expr
| Bool
otherwise -> do
GraphRefRelationalExpr
optSubExpr <- GraphRefRelationalExpr
-> GraphRefSOptRelationalExprM GraphRefRelationalExpr
optimizeGraphRefRelationalExpr GraphRefRelationalExpr
expr
forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a.
AttributeNamesBase a
-> RelationalExprBase a -> RelationalExprBase a
Project AttributeNamesBase GraphRefTransactionMarker
attrNameSet GraphRefRelationalExpr
optSubExpr)
optimizeGraphRefRelationalExpr (Union GraphRefRelationalExpr
exprA GraphRefRelationalExpr
exprB) = do
GraphRefRelationalExpr
optExprA <- GraphRefRelationalExpr
-> GraphRefSOptRelationalExprM GraphRefRelationalExpr
optimizeGraphRefRelationalExpr GraphRefRelationalExpr
exprA
GraphRefRelationalExpr
optExprB <- GraphRefRelationalExpr
-> GraphRefSOptRelationalExprM GraphRefRelationalExpr
optimizeGraphRefRelationalExpr GraphRefRelationalExpr
exprB
case (GraphRefRelationalExpr
optExprA, GraphRefRelationalExpr
optExprB) of
(Restrict GraphRefRestrictionPredicateExpr
predA (RelationVariable AttributeName
nameA GraphRefTransactionMarker
sA),
Restrict GraphRefRestrictionPredicateExpr
predB (RelationVariable AttributeName
nameB GraphRefTransactionMarker
sB)) | AttributeName
nameA forall a. Eq a => a -> a -> Bool
== AttributeName
nameB Bool -> Bool -> Bool
&& GraphRefTransactionMarker
sA forall a. Eq a => a -> a -> Bool
== GraphRefTransactionMarker
sB -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a.
RestrictionPredicateExprBase a
-> RelationalExprBase a -> RelationalExprBase a
Restrict (forall a.
RestrictionPredicateExprBase a
-> RestrictionPredicateExprBase a -> RestrictionPredicateExprBase a
AndPredicate GraphRefRestrictionPredicateExpr
predA GraphRefRestrictionPredicateExpr
predB) (forall a. AttributeName -> a -> RelationalExprBase a
RelationVariable AttributeName
nameA GraphRefTransactionMarker
sA))
(GraphRefRelationalExpr
exprA', GraphRefRelationalExpr
exprB') | forall a. RelationalExprBase a -> Bool
isEmptyRelationExpr GraphRefRelationalExpr
exprA' -> forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefRelationalExpr
exprB'
| forall a. RelationalExprBase a -> Bool
isEmptyRelationExpr GraphRefRelationalExpr
exprB' -> forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefRelationalExpr
exprA'
(GraphRefRelationalExpr, GraphRefRelationalExpr)
_ -> if GraphRefRelationalExpr
optExprA forall a. Eq a => a -> a -> Bool
== GraphRefRelationalExpr
optExprB then
forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefRelationalExpr
optExprA
else
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a.
RelationalExprBase a
-> RelationalExprBase a -> RelationalExprBase a
Union GraphRefRelationalExpr
optExprA GraphRefRelationalExpr
optExprB
optimizeGraphRefRelationalExpr (Join GraphRefRelationalExpr
exprA GraphRefRelationalExpr
exprB) = do
GraphRefRelationalExpr
optExprA <- GraphRefRelationalExpr
-> GraphRefSOptRelationalExprM GraphRefRelationalExpr
optimizeGraphRefRelationalExpr GraphRefRelationalExpr
exprA
GraphRefRelationalExpr
optExprB <- GraphRefRelationalExpr
-> GraphRefSOptRelationalExprM GraphRefRelationalExpr
optimizeGraphRefRelationalExpr GraphRefRelationalExpr
exprB
case (GraphRefRelationalExpr
optExprA, GraphRefRelationalExpr
optExprB) of
(Restrict GraphRefRestrictionPredicateExpr
predA (RelationVariable AttributeName
nameA GraphRefTransactionMarker
sA),
Restrict GraphRefRestrictionPredicateExpr
predB (RelationVariable AttributeName
nameB GraphRefTransactionMarker
sB)) | AttributeName
nameA forall a. Eq a => a -> a -> Bool
== AttributeName
nameB Bool -> Bool -> Bool
&& GraphRefTransactionMarker
sA forall a. Eq a => a -> a -> Bool
== GraphRefTransactionMarker
sB -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a.
RestrictionPredicateExprBase a
-> RelationalExprBase a -> RelationalExprBase a
Restrict (forall a.
RestrictionPredicateExprBase a
-> RestrictionPredicateExprBase a -> RestrictionPredicateExprBase a
AndPredicate GraphRefRestrictionPredicateExpr
predA GraphRefRestrictionPredicateExpr
predB) (forall a. AttributeName -> a -> RelationalExprBase a
RelationVariable AttributeName
nameA GraphRefTransactionMarker
sA))
(GraphRefRelationalExpr, GraphRefRelationalExpr)
_ -> if GraphRefRelationalExpr
optExprA forall a. Eq a => a -> a -> Bool
== GraphRefRelationalExpr
optExprB then
forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefRelationalExpr
optExprA
else
forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a.
RelationalExprBase a
-> RelationalExprBase a -> RelationalExprBase a
Join GraphRefRelationalExpr
optExprA GraphRefRelationalExpr
optExprB)
optimizeGraphRefRelationalExpr (Difference GraphRefRelationalExpr
exprA GraphRefRelationalExpr
exprB) = do
TransactionGraph
graph <- forall (m :: * -> *). AskGraphContext m => m TransactionGraph
askGraph
Maybe DatabaseContext
context <- GraphRefSOptRelationalExprM (Maybe DatabaseContext)
askMaybeContext
GraphRefRelationalExpr
optExprA <- GraphRefRelationalExpr
-> GraphRefSOptRelationalExprM GraphRefRelationalExpr
optimizeGraphRefRelationalExpr GraphRefRelationalExpr
exprA
GraphRefRelationalExpr
optExprB <- GraphRefRelationalExpr
-> GraphRefSOptRelationalExprM GraphRefRelationalExpr
optimizeGraphRefRelationalExpr GraphRefRelationalExpr
exprB
if GraphRefRelationalExpr
optExprA forall a. Eq a => a -> a -> Bool
== GraphRefRelationalExpr
optExprB then do
let eEmptyRel :: Either RelationalError Relation
eEmptyRel = forall a.
GraphRefRelationalExprEnv
-> GraphRefRelationalExprM a -> Either RelationalError a
runGraphRefRelationalExprM GraphRefRelationalExprEnv
gfEnv (GraphRefRelationalExpr -> GraphRefRelationalExprM Relation
typeForGraphRefRelationalExpr GraphRefRelationalExpr
optExprA)
gfEnv :: GraphRefRelationalExprEnv
gfEnv = Maybe DatabaseContext
-> TransactionGraph -> GraphRefRelationalExprEnv
freshGraphRefRelationalExprEnv Maybe DatabaseContext
context TransactionGraph
graph
case Either RelationalError Relation
eEmptyRel of
Left RelationalError
err -> forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError RelationalError
err
Right Relation
emptyRel -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Relation -> RelationalExprBase a
ExistingRelation Relation
emptyRel)
else
forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a.
RelationalExprBase a
-> RelationalExprBase a -> RelationalExprBase a
Difference GraphRefRelationalExpr
optExprA GraphRefRelationalExpr
optExprB)
optimizeGraphRefRelationalExpr e :: GraphRefRelationalExpr
e@Rename{} = forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefRelationalExpr
e
optimizeGraphRefRelationalExpr (Group AttributeNamesBase GraphRefTransactionMarker
oldAttrNames AttributeName
newAttrName GraphRefRelationalExpr
expr) =
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a.
AttributeNamesBase a
-> AttributeName -> RelationalExprBase a -> RelationalExprBase a
Group AttributeNamesBase GraphRefTransactionMarker
oldAttrNames AttributeName
newAttrName GraphRefRelationalExpr
expr
optimizeGraphRefRelationalExpr (Ungroup AttributeName
attrName GraphRefRelationalExpr
expr) =
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a.
AttributeName -> RelationalExprBase a -> RelationalExprBase a
Ungroup AttributeName
attrName GraphRefRelationalExpr
expr
optimizeGraphRefRelationalExpr (Restrict GraphRefRestrictionPredicateExpr
predicate GraphRefRelationalExpr
expr) = do
TransactionGraph
graph <- forall (m :: * -> *). AskGraphContext m => m TransactionGraph
askGraph
Maybe DatabaseContext
mctx <- GraphRefSOptRelationalExprM (Maybe DatabaseContext)
askMaybeContext
GraphRefRestrictionPredicateExpr
optimizedPredicate <- GraphRefRestrictionPredicateExpr
-> GraphRefSOptRelationalExprM GraphRefRestrictionPredicateExpr
applyStaticPredicateOptimization GraphRefRestrictionPredicateExpr
predicate
case GraphRefRestrictionPredicateExpr
optimizedPredicate of
GraphRefRestrictionPredicateExpr
optimizedPredicate' | forall a. RestrictionPredicateExprBase a -> Bool
isTrueExpr GraphRefRestrictionPredicateExpr
optimizedPredicate' -> GraphRefRelationalExpr
-> GraphRefSOptRelationalExprM GraphRefRelationalExpr
optimizeGraphRefRelationalExpr GraphRefRelationalExpr
expr
GraphRefRestrictionPredicateExpr
optimizedPredicate' | forall a. RestrictionPredicateExprBase a -> Bool
isFalseExpr GraphRefRestrictionPredicateExpr
optimizedPredicate' -> do
let attributesRel :: Either RelationalError Relation
attributesRel = forall a.
GraphRefRelationalExprEnv
-> GraphRefRelationalExprM a -> Either RelationalError a
runGraphRefRelationalExprM GraphRefRelationalExprEnv
gfEnv (GraphRefRelationalExpr -> GraphRefRelationalExprM Relation
typeForGraphRefRelationalExpr GraphRefRelationalExpr
expr)
gfEnv :: GraphRefRelationalExprEnv
gfEnv = Maybe DatabaseContext
-> TransactionGraph -> GraphRefRelationalExprEnv
freshGraphRefRelationalExprEnv Maybe DatabaseContext
mctx TransactionGraph
graph
case Either RelationalError Relation
attributesRel of
Left RelationalError
err -> forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError RelationalError
err
Right Relation
attributesRelA -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. Attributes -> RelationTupleSet -> RelationalExprBase a
MakeStaticRelation (Relation -> Attributes
attributes Relation
attributesRelA) RelationTupleSet
emptyTupleSet
| Bool
otherwise -> do
GraphRefRelationalExpr
optSubExpr <- GraphRefRelationalExpr
-> GraphRefSOptRelationalExprM GraphRefRelationalExpr
optimizeGraphRefRelationalExpr GraphRefRelationalExpr
expr
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a.
RestrictionPredicateExprBase a
-> RelationalExprBase a -> RelationalExprBase a
Restrict GraphRefRestrictionPredicateExpr
optimizedPredicate' GraphRefRelationalExpr
optSubExpr
optimizeGraphRefRelationalExpr e :: GraphRefRelationalExpr
e@(Equals GraphRefRelationalExpr
_ GraphRefRelationalExpr
_) = forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefRelationalExpr
e
optimizeGraphRefRelationalExpr e :: GraphRefRelationalExpr
e@(NotEquals GraphRefRelationalExpr
_ GraphRefRelationalExpr
_) = forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefRelationalExpr
e
optimizeGraphRefRelationalExpr e :: GraphRefRelationalExpr
e@(Extend ExtendTupleExprBase GraphRefTransactionMarker
_ GraphRefRelationalExpr
_) = forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefRelationalExpr
e
optimizeGraphRefRelationalExpr e :: GraphRefRelationalExpr
e@(With WithNamesAssocsBase GraphRefTransactionMarker
_ GraphRefRelationalExpr
_) = forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefRelationalExpr
e
optimizeGraphRefDatabaseContextExpr :: GraphRefDatabaseContextExpr -> GraphRefSOptDatabaseContextExprM GraphRefDatabaseContextExpr
optimizeGraphRefDatabaseContextExpr :: GraphRefDatabaseContextExpr
-> GraphRefSOptDatabaseContextExprM GraphRefDatabaseContextExpr
optimizeGraphRefDatabaseContextExpr x :: GraphRefDatabaseContextExpr
x@GraphRefDatabaseContextExpr
NoOperation = forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefDatabaseContextExpr
x
optimizeGraphRefDatabaseContextExpr x :: GraphRefDatabaseContextExpr
x@(Define AttributeName
_ [AttributeExprBase GraphRefTransactionMarker]
_) = forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefDatabaseContextExpr
x
optimizeGraphRefDatabaseContextExpr x :: GraphRefDatabaseContextExpr
x@(Undefine AttributeName
_) = forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefDatabaseContextExpr
x
optimizeGraphRefDatabaseContextExpr (Assign AttributeName
name GraphRefRelationalExpr
expr) = do
GraphRefRelationalExpr
optExpr <- forall a.
GraphRefSOptRelationalExprM a -> GraphRefSOptDatabaseContextExprM a
liftGraphRefRelExpr (GraphRefRelationalExpr
-> GraphRefSOptRelationalExprM GraphRefRelationalExpr
fullOptimizeGraphRefRelationalExpr GraphRefRelationalExpr
expr)
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a.
AttributeName -> RelationalExprBase a -> DatabaseContextExprBase a
Assign AttributeName
name GraphRefRelationalExpr
optExpr
optimizeGraphRefDatabaseContextExpr (Insert AttributeName
targetName GraphRefRelationalExpr
expr) = do
GraphRefRelationalExpr
optimizedExpr <- forall a.
GraphRefSOptRelationalExprM a -> GraphRefSOptDatabaseContextExprM a
liftGraphRefRelExpr (GraphRefRelationalExpr
-> GraphRefSOptRelationalExprM GraphRefRelationalExpr
fullOptimizeGraphRefRelationalExpr GraphRefRelationalExpr
expr)
if forall a. RelationalExprBase a -> Bool
isEmptyRelationExpr GraphRefRelationalExpr
optimizedExpr then
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. DatabaseContextExprBase a
NoOperation
else
case GraphRefRelationalExpr
optimizedExpr of
RelationVariable AttributeName
insName GraphRefTransactionMarker
_ | AttributeName
insName forall a. Eq a => a -> a -> Bool
== AttributeName
targetName -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. DatabaseContextExprBase a
NoOperation
GraphRefRelationalExpr
_ -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a.
AttributeName -> RelationalExprBase a -> DatabaseContextExprBase a
Insert AttributeName
targetName GraphRefRelationalExpr
optimizedExpr)
optimizeGraphRefDatabaseContextExpr (Delete AttributeName
name GraphRefRestrictionPredicateExpr
predicate) =
forall a.
AttributeName
-> RestrictionPredicateExprBase a -> DatabaseContextExprBase a
Delete AttributeName
name forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a.
GraphRefSOptRelationalExprM a -> GraphRefSOptDatabaseContextExprM a
liftGraphRefRelExpr (GraphRefRestrictionPredicateExpr
-> GraphRefSOptRelationalExprM GraphRefRestrictionPredicateExpr
applyStaticPredicateOptimization GraphRefRestrictionPredicateExpr
predicate)
optimizeGraphRefDatabaseContextExpr (Update AttributeName
name AttributeNameAtomExprMap
upmap GraphRefRestrictionPredicateExpr
predicate) =
forall a.
AttributeName
-> AttributeNameAtomExprMap
-> RestrictionPredicateExprBase a
-> DatabaseContextExprBase a
Update AttributeName
name AttributeNameAtomExprMap
upmap forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a.
GraphRefSOptRelationalExprM a -> GraphRefSOptDatabaseContextExprM a
liftGraphRefRelExpr (GraphRefRestrictionPredicateExpr
-> GraphRefSOptRelationalExprM GraphRefRestrictionPredicateExpr
applyStaticPredicateOptimization GraphRefRestrictionPredicateExpr
predicate)
optimizeGraphRefDatabaseContextExpr dep :: GraphRefDatabaseContextExpr
dep@(AddInclusionDependency AttributeName
_ InclusionDependency
_) = forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefDatabaseContextExpr
dep
optimizeGraphRefDatabaseContextExpr (RemoveInclusionDependency AttributeName
name) = forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. AttributeName -> DatabaseContextExprBase a
RemoveInclusionDependency AttributeName
name)
optimizeGraphRefDatabaseContextExpr (AddNotification AttributeName
name RelationalExpr
triggerExpr RelationalExpr
resultOldExpr RelationalExpr
resultNewExpr) =
forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a.
AttributeName
-> RelationalExpr
-> RelationalExpr
-> RelationalExpr
-> DatabaseContextExprBase a
AddNotification AttributeName
name RelationalExpr
triggerExpr RelationalExpr
resultOldExpr RelationalExpr
resultNewExpr)
optimizeGraphRefDatabaseContextExpr notif :: GraphRefDatabaseContextExpr
notif@(RemoveNotification AttributeName
_) = forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefDatabaseContextExpr
notif
optimizeGraphRefDatabaseContextExpr c :: GraphRefDatabaseContextExpr
c@(AddTypeConstructor TypeConstructorDef
_ [DataConstructorDef]
_) = forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefDatabaseContextExpr
c
optimizeGraphRefDatabaseContextExpr c :: GraphRefDatabaseContextExpr
c@(RemoveTypeConstructor AttributeName
_) = forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefDatabaseContextExpr
c
optimizeGraphRefDatabaseContextExpr c :: GraphRefDatabaseContextExpr
c@(RemoveAtomFunction AttributeName
_) = forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefDatabaseContextExpr
c
optimizeGraphRefDatabaseContextExpr c :: GraphRefDatabaseContextExpr
c@(RemoveDatabaseContextFunction AttributeName
_) = forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefDatabaseContextExpr
c
optimizeGraphRefDatabaseContextExpr c :: GraphRefDatabaseContextExpr
c@(ExecuteDatabaseContextFunction AttributeName
_ [AtomExprBase GraphRefTransactionMarker]
_) = forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefDatabaseContextExpr
c
optimizeGraphRefDatabaseContextExpr c :: GraphRefDatabaseContextExpr
c@AddRegisteredQuery{} = forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefDatabaseContextExpr
c
optimizeGraphRefDatabaseContextExpr c :: GraphRefDatabaseContextExpr
c@RemoveRegisteredQuery{} = forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefDatabaseContextExpr
c
optimizeGraphRefDatabaseContextExpr (MultipleExpr [GraphRefDatabaseContextExpr]
exprs) = do
DatabaseContext
context <- forall (m :: * -> *). AskGraphContext m => m DatabaseContext
askContext
TransactionGraph
graph <- forall (m :: * -> *). AskGraphContext m => m TransactionGraph
askGraph
TransactionId
parentId <- GraphRefSOptDatabaseContextExprM TransactionId
askTransId
let emptyRvs :: DatabaseContext -> DatabaseContext
emptyRvs DatabaseContext
ctx = DatabaseContext
ctx { relationVariables :: RelationVariables
relationVariables = RelationVariables -> RelationVariables
mkEmptyRelVars (DatabaseContext -> RelationVariables
relationVariables DatabaseContext
ctx) }
dbcEnv :: DatabaseContextEvalEnv
dbcEnv = TransactionId -> TransactionGraph -> DatabaseContextEvalEnv
mkDatabaseContextEvalEnv TransactionId
parentId TransactionGraph
graph
folder :: (DatabaseContext, [GraphRefDatabaseContextExpr])
-> GraphRefDatabaseContextExpr
-> m (DatabaseContext, [GraphRefDatabaseContextExpr])
folder (DatabaseContext
ctx, [GraphRefDatabaseContextExpr]
expracc) GraphRefDatabaseContextExpr
expr = do
case forall a.
TransactionId
-> DatabaseContext
-> TransactionGraph
-> GraphRefSOptDatabaseContextExprM a
-> Either RelationalError a
runGraphRefSOptDatabaseContextExprM TransactionId
parentId DatabaseContext
ctx TransactionGraph
graph (GraphRefDatabaseContextExpr
-> GraphRefSOptDatabaseContextExprM GraphRefDatabaseContextExpr
optimizeGraphRefDatabaseContextExpr GraphRefDatabaseContextExpr
expr) of
Left RelationalError
err -> forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError RelationalError
err
Right GraphRefDatabaseContextExpr
optExpr ->
case DatabaseContext
-> DatabaseContextEvalEnv
-> DatabaseContextEvalMonad ()
-> Either RelationalError DatabaseContextEvalState
runDatabaseContextEvalMonad DatabaseContext
ctx DatabaseContextEvalEnv
dbcEnv (GraphRefDatabaseContextExpr -> DatabaseContextEvalMonad ()
evalGraphRefDatabaseContextExpr GraphRefDatabaseContextExpr
optExpr) of
Left RelationalError
err -> forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError RelationalError
err
Right DatabaseContextEvalState
dbcState ->
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DatabaseContext -> DatabaseContext
emptyRvs forall a b. (a -> b) -> a -> b
$ DatabaseContextEvalState -> DatabaseContext
dbc_context DatabaseContextEvalState
dbcState, [GraphRefDatabaseContextExpr]
expracc forall a. [a] -> [a] -> [a]
++ [GraphRefDatabaseContextExpr
optExpr])
(DatabaseContext
_, [GraphRefDatabaseContextExpr]
exprs') <- forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM forall {m :: * -> *}.
MonadError RelationalError m =>
(DatabaseContext, [GraphRefDatabaseContextExpr])
-> GraphRefDatabaseContextExpr
-> m (DatabaseContext, [GraphRefDatabaseContextExpr])
folder (DatabaseContext
context,[]) [GraphRefDatabaseContextExpr]
exprs
forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. [DatabaseContextExprBase a] -> DatabaseContextExprBase a
MultipleExpr [GraphRefDatabaseContextExpr]
exprs')
applyStaticPredicateOptimization :: GraphRefRestrictionPredicateExpr -> GraphRefSOptRelationalExprM GraphRefRestrictionPredicateExpr
applyStaticPredicateOptimization :: GraphRefRestrictionPredicateExpr
-> GraphRefSOptRelationalExprM GraphRefRestrictionPredicateExpr
applyStaticPredicateOptimization GraphRefRestrictionPredicateExpr
predi = do
GraphRefRestrictionPredicateExpr
optPred <- case GraphRefRestrictionPredicateExpr
predi of
AndPredicate GraphRefRestrictionPredicateExpr
pred1 GraphRefRestrictionPredicateExpr
pred2 -> do
GraphRefRestrictionPredicateExpr
optPredA <- GraphRefRestrictionPredicateExpr
-> GraphRefSOptRelationalExprM GraphRefRestrictionPredicateExpr
applyStaticPredicateOptimization GraphRefRestrictionPredicateExpr
pred1
GraphRefRestrictionPredicateExpr
optPredB <- GraphRefRestrictionPredicateExpr
-> GraphRefSOptRelationalExprM GraphRefRestrictionPredicateExpr
applyStaticPredicateOptimization GraphRefRestrictionPredicateExpr
pred2
if GraphRefRestrictionPredicateExpr
optPredA forall a. Eq a => a -> a -> Bool
== GraphRefRestrictionPredicateExpr
optPredB then
forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefRestrictionPredicateExpr
optPredA
else
forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a.
RestrictionPredicateExprBase a
-> RestrictionPredicateExprBase a -> RestrictionPredicateExprBase a
AndPredicate GraphRefRestrictionPredicateExpr
optPredA GraphRefRestrictionPredicateExpr
optPredB)
OrPredicate GraphRefRestrictionPredicateExpr
pred1 GraphRefRestrictionPredicateExpr
pred2 -> do
GraphRefRestrictionPredicateExpr
optPredA <- GraphRefRestrictionPredicateExpr
-> GraphRefSOptRelationalExprM GraphRefRestrictionPredicateExpr
applyStaticPredicateOptimization GraphRefRestrictionPredicateExpr
pred1
GraphRefRestrictionPredicateExpr
optPredB <- GraphRefRestrictionPredicateExpr
-> GraphRefSOptRelationalExprM GraphRefRestrictionPredicateExpr
applyStaticPredicateOptimization GraphRefRestrictionPredicateExpr
pred2
if (GraphRefRestrictionPredicateExpr
optPredA forall a. Eq a => a -> a -> Bool
== GraphRefRestrictionPredicateExpr
optPredB) Bool -> Bool -> Bool
|| forall a. RestrictionPredicateExprBase a -> Bool
isTrueExpr GraphRefRestrictionPredicateExpr
optPredA then
forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefRestrictionPredicateExpr
optPredA
else if forall a. RestrictionPredicateExprBase a -> Bool
isTrueExpr GraphRefRestrictionPredicateExpr
optPredB then
forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefRestrictionPredicateExpr
optPredB
else
forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a.
RestrictionPredicateExprBase a
-> RestrictionPredicateExprBase a -> RestrictionPredicateExprBase a
OrPredicate GraphRefRestrictionPredicateExpr
optPredA GraphRefRestrictionPredicateExpr
optPredB)
AttributeEqualityPredicate AttributeName
attrNameA (AttributeAtomExpr AttributeName
attrNameB) ->
if AttributeName
attrNameA forall a. Eq a => a -> a -> Bool
== AttributeName
attrNameB then
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. RestrictionPredicateExprBase a
TruePredicate
else
forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefRestrictionPredicateExpr
predi
AttributeEqualityPredicate{} -> forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefRestrictionPredicateExpr
predi
GraphRefRestrictionPredicateExpr
TruePredicate -> forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefRestrictionPredicateExpr
predi
NotPredicate{} -> forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefRestrictionPredicateExpr
predi
RelationalExprPredicate{} -> forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefRestrictionPredicateExpr
predi
AtomExprPredicate{} -> forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefRestrictionPredicateExpr
predi
let attrMap :: Map AttributeName (AtomExprBase GraphRefTransactionMarker)
attrMap = GraphRefRestrictionPredicateExpr
-> Map AttributeName (AtomExprBase GraphRefTransactionMarker)
findStaticRestrictionPredicates GraphRefRestrictionPredicateExpr
optPred
forall (f :: * -> *) a. Applicative f => a -> f a
pure (GraphRefRestrictionPredicateExpr
-> Map AttributeName (AtomExprBase GraphRefTransactionMarker)
-> GraphRefRestrictionPredicateExpr
replaceStaticAtomExprs GraphRefRestrictionPredicateExpr
optPred Map AttributeName (AtomExprBase GraphRefTransactionMarker)
attrMap)
isTrueExpr :: RestrictionPredicateExprBase a -> Bool
isTrueExpr :: forall a. RestrictionPredicateExprBase a -> Bool
isTrueExpr RestrictionPredicateExprBase a
TruePredicate = Bool
True
isTrueExpr (AtomExprPredicate (NakedAtomExpr (BoolAtom Bool
True))) = Bool
True
isTrueExpr RestrictionPredicateExprBase a
_ = Bool
False
isFalseExpr :: RestrictionPredicateExprBase a -> Bool
isFalseExpr :: forall a. RestrictionPredicateExprBase a -> Bool
isFalseExpr (NotPredicate RestrictionPredicateExprBase a
expr) = forall a. RestrictionPredicateExprBase a -> Bool
isTrueExpr RestrictionPredicateExprBase a
expr
isFalseExpr (AtomExprPredicate (NakedAtomExpr (BoolAtom Bool
False))) = Bool
True
isFalseExpr RestrictionPredicateExprBase a
_ = Bool
False
isEmptyRelationExpr :: RelationalExprBase a -> Bool
isEmptyRelationExpr :: forall a. RelationalExprBase a -> Bool
isEmptyRelationExpr (MakeRelationFromExprs Maybe [AttributeExprBase a]
_ (TupleExprs a
_ [])) = Bool
True
isEmptyRelationExpr (MakeStaticRelation Attributes
_ RelationTupleSet
tupSet) = forall (t :: * -> *) a. Foldable t => t a -> Bool
null (RelationTupleSet -> [RelationTuple]
asList RelationTupleSet
tupSet)
isEmptyRelationExpr (ExistingRelation Relation
rel) = Relation
rel forall a. Eq a => a -> a -> Bool
== Attributes -> Relation
emptyRelationWithAttrs (Relation -> Attributes
attributes Relation
rel)
isEmptyRelationExpr RelationalExprBase a
_ = Bool
False
replaceStaticAtomExprs :: GraphRefRestrictionPredicateExpr -> M.Map AttributeName GraphRefAtomExpr -> GraphRefRestrictionPredicateExpr
replaceStaticAtomExprs :: GraphRefRestrictionPredicateExpr
-> Map AttributeName (AtomExprBase GraphRefTransactionMarker)
-> GraphRefRestrictionPredicateExpr
replaceStaticAtomExprs GraphRefRestrictionPredicateExpr
predIn Map AttributeName (AtomExprBase GraphRefTransactionMarker)
replaceMap = case GraphRefRestrictionPredicateExpr
predIn of
AttributeEqualityPredicate AttributeName
newAttrName (AttributeAtomExpr AttributeName
matchName) -> case forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup AttributeName
matchName Map AttributeName (AtomExprBase GraphRefTransactionMarker)
replaceMap of
Maybe (AtomExprBase GraphRefTransactionMarker)
Nothing -> GraphRefRestrictionPredicateExpr
predIn
Just AtomExprBase GraphRefTransactionMarker
newVal -> forall a.
AttributeName -> AtomExprBase a -> RestrictionPredicateExprBase a
AttributeEqualityPredicate AttributeName
newAttrName AtomExprBase GraphRefTransactionMarker
newVal
AttributeEqualityPredicate{} -> GraphRefRestrictionPredicateExpr
predIn
AndPredicate GraphRefRestrictionPredicateExpr
pred1 GraphRefRestrictionPredicateExpr
pred2 -> forall a.
RestrictionPredicateExprBase a
-> RestrictionPredicateExprBase a -> RestrictionPredicateExprBase a
AndPredicate (GraphRefRestrictionPredicateExpr
-> Map AttributeName (AtomExprBase GraphRefTransactionMarker)
-> GraphRefRestrictionPredicateExpr
replaceStaticAtomExprs GraphRefRestrictionPredicateExpr
pred1 Map AttributeName (AtomExprBase GraphRefTransactionMarker)
replaceMap) (GraphRefRestrictionPredicateExpr
-> Map AttributeName (AtomExprBase GraphRefTransactionMarker)
-> GraphRefRestrictionPredicateExpr
replaceStaticAtomExprs GraphRefRestrictionPredicateExpr
pred2 Map AttributeName (AtomExprBase GraphRefTransactionMarker)
replaceMap)
OrPredicate GraphRefRestrictionPredicateExpr
pred1 GraphRefRestrictionPredicateExpr
pred2 -> forall a.
RestrictionPredicateExprBase a
-> RestrictionPredicateExprBase a -> RestrictionPredicateExprBase a
OrPredicate (GraphRefRestrictionPredicateExpr
-> Map AttributeName (AtomExprBase GraphRefTransactionMarker)
-> GraphRefRestrictionPredicateExpr
replaceStaticAtomExprs GraphRefRestrictionPredicateExpr
pred1 Map AttributeName (AtomExprBase GraphRefTransactionMarker)
replaceMap) (GraphRefRestrictionPredicateExpr
-> Map AttributeName (AtomExprBase GraphRefTransactionMarker)
-> GraphRefRestrictionPredicateExpr
replaceStaticAtomExprs GraphRefRestrictionPredicateExpr
pred2 Map AttributeName (AtomExprBase GraphRefTransactionMarker)
replaceMap)
NotPredicate GraphRefRestrictionPredicateExpr
pred1 -> forall a.
RestrictionPredicateExprBase a -> RestrictionPredicateExprBase a
NotPredicate (GraphRefRestrictionPredicateExpr
-> Map AttributeName (AtomExprBase GraphRefTransactionMarker)
-> GraphRefRestrictionPredicateExpr
replaceStaticAtomExprs GraphRefRestrictionPredicateExpr
pred1 Map AttributeName (AtomExprBase GraphRefTransactionMarker)
replaceMap)
GraphRefRestrictionPredicateExpr
TruePredicate -> GraphRefRestrictionPredicateExpr
predIn
RelationalExprPredicate{} -> GraphRefRestrictionPredicateExpr
predIn
AtomExprPredicate{} -> GraphRefRestrictionPredicateExpr
predIn
findStaticRestrictionPredicates :: GraphRefRestrictionPredicateExpr -> M.Map AttributeName GraphRefAtomExpr
findStaticRestrictionPredicates :: GraphRefRestrictionPredicateExpr
-> Map AttributeName (AtomExprBase GraphRefTransactionMarker)
findStaticRestrictionPredicates (AttributeEqualityPredicate AttributeName
attrName AtomExprBase GraphRefTransactionMarker
atomExpr) =
case AtomExprBase GraphRefTransactionMarker
atomExpr of
val :: AtomExprBase GraphRefTransactionMarker
val@NakedAtomExpr{} -> forall k a. k -> a -> Map k a
M.singleton AttributeName
attrName AtomExprBase GraphRefTransactionMarker
val
val :: AtomExprBase GraphRefTransactionMarker
val@ConstructedAtomExpr{} -> forall k a. k -> a -> Map k a
M.singleton AttributeName
attrName AtomExprBase GraphRefTransactionMarker
val
AtomExprBase GraphRefTransactionMarker
_ -> forall k a. Map k a
M.empty
findStaticRestrictionPredicates (AndPredicate GraphRefRestrictionPredicateExpr
pred1 GraphRefRestrictionPredicateExpr
pred2) =
forall k a. Ord k => Map k a -> Map k a -> Map k a
M.union (GraphRefRestrictionPredicateExpr
-> Map AttributeName (AtomExprBase GraphRefTransactionMarker)
findStaticRestrictionPredicates GraphRefRestrictionPredicateExpr
pred1) (GraphRefRestrictionPredicateExpr
-> Map AttributeName (AtomExprBase GraphRefTransactionMarker)
findStaticRestrictionPredicates GraphRefRestrictionPredicateExpr
pred2)
findStaticRestrictionPredicates (OrPredicate GraphRefRestrictionPredicateExpr
pred1 GraphRefRestrictionPredicateExpr
pred2) =
forall k a. Ord k => Map k a -> Map k a -> Map k a
M.union (GraphRefRestrictionPredicateExpr
-> Map AttributeName (AtomExprBase GraphRefTransactionMarker)
findStaticRestrictionPredicates GraphRefRestrictionPredicateExpr
pred1) (GraphRefRestrictionPredicateExpr
-> Map AttributeName (AtomExprBase GraphRefTransactionMarker)
findStaticRestrictionPredicates GraphRefRestrictionPredicateExpr
pred2)
findStaticRestrictionPredicates (NotPredicate GraphRefRestrictionPredicateExpr
predi) = GraphRefRestrictionPredicateExpr
-> Map AttributeName (AtomExprBase GraphRefTransactionMarker)
findStaticRestrictionPredicates GraphRefRestrictionPredicateExpr
predi
findStaticRestrictionPredicates GraphRefRestrictionPredicateExpr
TruePredicate = forall k a. Map k a
M.empty
findStaticRestrictionPredicates RelationalExprPredicate{} = forall k a. Map k a
M.empty
findStaticRestrictionPredicates AtomExprPredicate{} = forall k a. Map k a
M.empty
isStaticAtomExpr :: AtomExpr -> Bool
isStaticAtomExpr :: AtomExpr -> Bool
isStaticAtomExpr NakedAtomExpr{} = Bool
True
isStaticAtomExpr SubrelationAttributeAtomExpr{} = Bool
False
isStaticAtomExpr ConstructedAtomExpr{} = Bool
True
isStaticAtomExpr AttributeAtomExpr{} = Bool
False
isStaticAtomExpr FunctionAtomExpr{} = Bool
False
isStaticAtomExpr IfThenAtomExpr{} = Bool
False
isStaticAtomExpr RelationAtomExpr{} = Bool
False
applyStaticJoinElimination :: GraphRefRelationalExpr -> GraphRefSOptRelationalExprM GraphRefRelationalExpr
applyStaticJoinElimination :: GraphRefRelationalExpr
-> GraphRefSOptRelationalExprM GraphRefRelationalExpr
applyStaticJoinElimination expr :: GraphRefRelationalExpr
expr@(Project AttributeNamesBase GraphRefTransactionMarker
attrNameSet (Join GraphRefRelationalExpr
exprA GraphRefRelationalExpr
exprB)) = do
TransactionGraph
graph <- forall (m :: * -> *). AskGraphContext m => m TransactionGraph
askGraph
case GraphRefRelationalExpr
-> GraphRefRelationalExpr -> Maybe GraphRefTransactionMarker
inSameTransaction GraphRefRelationalExpr
exprA GraphRefRelationalExpr
exprB of
Maybe GraphRefTransactionMarker
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefRelationalExpr
expr
Just GraphRefTransactionMarker
marker -> do
DatabaseContext
commonContext <- case GraphRefTransactionMarker
marker of
GraphRefTransactionMarker
UncommittedContextMarker -> forall (m :: * -> *). AskGraphContext m => m DatabaseContext
askContext
TransactionMarker TransactionId
tid -> Transaction -> DatabaseContext
concreteDatabaseContext forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (forall (m :: * -> *) e a. Monad m => Either e a -> ExceptT e m a
except (TransactionId
-> TransactionGraph -> Either RelationalError Transaction
transactionForId TransactionId
tid TransactionGraph
graph))
let typeForExpr :: GraphRefRelationalExpr -> t (ExceptT RelationalError m) Relation
typeForExpr GraphRefRelationalExpr
e = forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) e a. Monad m => Either e a -> ExceptT e m a
except forall a b. (a -> b) -> a -> b
$ forall a.
GraphRefRelationalExprEnv
-> GraphRefRelationalExprM a -> Either RelationalError a
runGraphRefRelationalExprM GraphRefRelationalExprEnv
gfEnv (GraphRefRelationalExpr -> GraphRefRelationalExprM Relation
typeForGraphRefRelationalExpr GraphRefRelationalExpr
e)
gfEnv :: GraphRefRelationalExprEnv
gfEnv = Maybe DatabaseContext
-> TransactionGraph -> GraphRefRelationalExprEnv
freshGraphRefRelationalExprEnv (forall a. a -> Maybe a
Just DatabaseContext
commonContext) TransactionGraph
graph
Relation
projType <- forall {t :: (* -> *) -> * -> *} {m :: * -> *}.
(MonadTrans t, Monad m) =>
GraphRefRelationalExpr -> t (ExceptT RelationalError m) Relation
typeForExpr GraphRefRelationalExpr
expr
Relation
typeA <- forall {t :: (* -> *) -> * -> *} {m :: * -> *}.
(MonadTrans t, Monad m) =>
GraphRefRelationalExpr -> t (ExceptT RelationalError m) Relation
typeForExpr GraphRefRelationalExpr
exprA
Relation
typeB <- forall {t :: (* -> *) -> * -> *} {m :: * -> *}.
(MonadTrans t, Monad m) =>
GraphRefRelationalExpr -> t (ExceptT RelationalError m) Relation
typeForExpr GraphRefRelationalExpr
exprB
let matchesProjectionAttributes :: Maybe
((GraphRefRelationalExpr, Relation),
(GraphRefRelationalExpr, Relation))
matchesProjectionAttributes
| Relation -> Set AttributeName
attrNames Relation
projType forall a. Ord a => Set a -> Set a -> Bool
`S.isSubsetOf` Relation -> Set AttributeName
attrNames Relation
typeA =
forall a. a -> Maybe a
Just ((GraphRefRelationalExpr
exprA, Relation
typeA), (GraphRefRelationalExpr
exprB, Relation
typeB))
| Relation -> Set AttributeName
attrNames Relation
projType forall a. Ord a => Set a -> Set a -> Bool
`S.isSubsetOf` Relation -> Set AttributeName
attrNames Relation
typeB =
forall a. a -> Maybe a
Just ((GraphRefRelationalExpr
exprB, Relation
typeB), (GraphRefRelationalExpr
exprA, Relation
typeA))
| Bool
otherwise =
forall a. Maybe a
Nothing
attrNames :: Relation -> Set AttributeName
attrNames = Attributes -> Set AttributeName
A.attributeNameSet forall b c a. (b -> c) -> (a -> b) -> a -> c
. Relation -> Attributes
attributes
case Maybe
((GraphRefRelationalExpr, Relation),
(GraphRefRelationalExpr, Relation))
matchesProjectionAttributes of
Maybe
((GraphRefRelationalExpr, Relation),
(GraphRefRelationalExpr, Relation))
Nothing ->
forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefRelationalExpr
expr
Just ((GraphRefRelationalExpr
joinedExpr, Relation
joinedType), (GraphRefRelationalExpr
unjoinedExpr, Relation
_)) -> do
let incDeps :: InclusionDependencies
incDeps = DatabaseContext -> InclusionDependencies
inclusionDependencies DatabaseContext
commonContext
fkConstraint :: Either RelationalError Bool
fkConstraint = forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM forall {f :: * -> *}.
Applicative f =>
Bool -> InclusionDependency -> f Bool
isFkConstraint Bool
False InclusionDependencies
incDeps
isFkConstraint :: Bool -> InclusionDependency -> f Bool
isFkConstraint Bool
acc (InclusionDependency (Project AttributeNamesBase ()
subAttrNames RelationalExpr
subrv) (Project AttributeNamesBase ()
_ RelationalExpr
superrv)) = do
let gfSubAttrNames :: AttributeNamesBase GraphRefTransactionMarker
gfSubAttrNames = forall {a}. ProcessExprM a -> a
processM (AttributeNamesBase ()
-> ProcessExprM (AttributeNamesBase GraphRefTransactionMarker)
processAttributeNames AttributeNamesBase ()
subAttrNames)
gfSubRv :: GraphRefRelationalExpr
gfSubRv = forall {a}. ProcessExprM a -> a
processM (RelationalExpr -> ProcessExprM GraphRefRelationalExpr
processRelationalExpr RelationalExpr
subrv)
gfSuperRv :: GraphRefRelationalExpr
gfSuperRv = forall {a}. ProcessExprM a -> a
processM (RelationalExpr -> ProcessExprM GraphRefRelationalExpr
processRelationalExpr RelationalExpr
superrv)
processM :: ProcessExprM a -> a
processM = forall a. GraphRefTransactionMarker -> ProcessExprM a -> a
runProcessExprM GraphRefTransactionMarker
marker
case forall a.
GraphRefRelationalExprEnv
-> GraphRefRelationalExprM a -> Either RelationalError a
runGraphRefRelationalExprM GraphRefRelationalExprEnv
gfEnv (AttributeNamesBase GraphRefTransactionMarker
-> GraphRefRelationalExpr
-> GraphRefRelationalExprM (Set AttributeName)
evalGraphRefAttributeNames AttributeNamesBase GraphRefTransactionMarker
gfSubAttrNames GraphRefRelationalExpr
expr) of
Left RelationalError
_ -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
acc
Right Set AttributeName
subAttrNameSet ->
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool
acc Bool -> Bool -> Bool
|| (GraphRefRelationalExpr
joinedExpr forall a. Eq a => a -> a -> Bool
== GraphRefRelationalExpr
gfSubRv Bool -> Bool -> Bool
&&
GraphRefRelationalExpr
unjoinedExpr forall a. Eq a => a -> a -> Bool
== GraphRefRelationalExpr
gfSuperRv Bool -> Bool -> Bool
&&
Set AttributeName -> Set AttributeName -> Bool
A.attributeNamesContained Set AttributeName
subAttrNameSet (Attributes -> Set AttributeName
A.attributeNameSet (Relation -> Attributes
attributes Relation
joinedType))
))
isFkConstraint Bool
acc InclusionDependency
_ = forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
acc
case Either RelationalError Bool
fkConstraint of
Right Bool
True ->
GraphRefRelationalExpr
-> GraphRefSOptRelationalExprM GraphRefRelationalExpr
optimizeGraphRefRelationalExpr (forall a.
AttributeNamesBase a
-> RelationalExprBase a -> RelationalExprBase a
Project AttributeNamesBase GraphRefTransactionMarker
attrNameSet GraphRefRelationalExpr
joinedExpr)
Right Bool
False ->
forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefRelationalExpr
expr
Left RelationalError
err -> forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError RelationalError
err
applyStaticJoinElimination GraphRefRelationalExpr
expr = forall (f :: * -> *) a. Applicative f => a -> f a
pure GraphRefRelationalExpr
expr
applyStaticRestrictionCollapse :: GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionCollapse :: GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionCollapse GraphRefRelationalExpr
expr =
case GraphRefRelationalExpr
expr of
MakeRelationFromExprs Maybe [AttributeExprBase GraphRefTransactionMarker]
_ TupleExprsBase GraphRefTransactionMarker
_ -> GraphRefRelationalExpr
expr
MakeStaticRelation Attributes
_ RelationTupleSet
_ -> GraphRefRelationalExpr
expr
ExistingRelation Relation
_ -> GraphRefRelationalExpr
expr
RelationValuedAttribute{} -> GraphRefRelationalExpr
expr
RelationVariable AttributeName
_ GraphRefTransactionMarker
_ -> GraphRefRelationalExpr
expr
With WithNamesAssocsBase GraphRefTransactionMarker
_ GraphRefRelationalExpr
_ -> GraphRefRelationalExpr
expr
Project AttributeNamesBase GraphRefTransactionMarker
attrs GraphRefRelationalExpr
subexpr ->
forall a.
AttributeNamesBase a
-> RelationalExprBase a -> RelationalExprBase a
Project AttributeNamesBase GraphRefTransactionMarker
attrs (GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionCollapse GraphRefRelationalExpr
subexpr)
Union GraphRefRelationalExpr
sub1 GraphRefRelationalExpr
sub2 ->
forall a.
RelationalExprBase a
-> RelationalExprBase a -> RelationalExprBase a
Union (GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionCollapse GraphRefRelationalExpr
sub1) (GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionCollapse GraphRefRelationalExpr
sub2)
Join GraphRefRelationalExpr
sub1 GraphRefRelationalExpr
sub2 ->
forall a.
RelationalExprBase a
-> RelationalExprBase a -> RelationalExprBase a
Join (GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionCollapse GraphRefRelationalExpr
sub1) (GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionCollapse GraphRefRelationalExpr
sub2)
Rename Set (AttributeName, AttributeName)
attrs GraphRefRelationalExpr
sub ->
forall a.
Set (AttributeName, AttributeName)
-> RelationalExprBase a -> RelationalExprBase a
Rename Set (AttributeName, AttributeName)
attrs (GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionCollapse GraphRefRelationalExpr
sub)
Difference GraphRefRelationalExpr
sub1 GraphRefRelationalExpr
sub2 ->
forall a.
RelationalExprBase a
-> RelationalExprBase a -> RelationalExprBase a
Difference (GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionCollapse GraphRefRelationalExpr
sub1) (GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionCollapse GraphRefRelationalExpr
sub2)
Group AttributeNamesBase GraphRefTransactionMarker
n1 AttributeName
n2 GraphRefRelationalExpr
sub ->
forall a.
AttributeNamesBase a
-> AttributeName -> RelationalExprBase a -> RelationalExprBase a
Group AttributeNamesBase GraphRefTransactionMarker
n1 AttributeName
n2 (GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionCollapse GraphRefRelationalExpr
sub)
Ungroup AttributeName
n1 GraphRefRelationalExpr
sub ->
forall a.
AttributeName -> RelationalExprBase a -> RelationalExprBase a
Ungroup AttributeName
n1 (GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionCollapse GraphRefRelationalExpr
sub)
Equals GraphRefRelationalExpr
sub1 GraphRefRelationalExpr
sub2 ->
forall a.
RelationalExprBase a
-> RelationalExprBase a -> RelationalExprBase a
Equals (GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionCollapse GraphRefRelationalExpr
sub1) (GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionCollapse GraphRefRelationalExpr
sub2)
NotEquals GraphRefRelationalExpr
sub1 GraphRefRelationalExpr
sub2 ->
forall a.
RelationalExprBase a
-> RelationalExprBase a -> RelationalExprBase a
NotEquals (GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionCollapse GraphRefRelationalExpr
sub1) (GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionCollapse GraphRefRelationalExpr
sub2)
Extend ExtendTupleExprBase GraphRefTransactionMarker
n GraphRefRelationalExpr
sub ->
forall a.
ExtendTupleExprBase a
-> RelationalExprBase a -> RelationalExprBase a
Extend ExtendTupleExprBase GraphRefTransactionMarker
n (GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionCollapse GraphRefRelationalExpr
sub)
Restrict GraphRefRestrictionPredicateExpr
firstPred GraphRefRelationalExpr
_ ->
let (GraphRefRelationalExpr
finalExpr, [GraphRefRelationalExpr]
restrictions) = case forall a. RelationalExprBase a -> [RelationalExprBase a]
sequentialRestrictions GraphRefRelationalExpr
expr of
[] -> (forall a. HasCallStack => a
undefined, [])
GraphRefRelationalExpr
x : [GraphRefRelationalExpr]
xs -> (forall a. NonEmpty a -> a
NE.last forall a b. (a -> b) -> a -> b
$ GraphRefRelationalExpr
x forall a. a -> [a] -> NonEmpty a
:| [GraphRefRelationalExpr]
xs, [GraphRefRelationalExpr]
xs)
optFinalExpr :: GraphRefRelationalExpr
optFinalExpr = case GraphRefRelationalExpr
finalExpr of
Restrict GraphRefRestrictionPredicateExpr
_ GraphRefRelationalExpr
subexpr -> GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionCollapse GraphRefRelationalExpr
subexpr
GraphRefRelationalExpr
otherExpr -> GraphRefRelationalExpr
otherExpr
andPreds :: GraphRefRestrictionPredicateExpr
andPreds = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall {a}.
RelationalExprBase a
-> RestrictionPredicateExprBase a -> RestrictionPredicateExprBase a
folder GraphRefRestrictionPredicateExpr
firstPred [GraphRefRelationalExpr]
restrictions
folder :: RelationalExprBase a
-> RestrictionPredicateExprBase a -> RestrictionPredicateExprBase a
folder (Restrict RestrictionPredicateExprBase a
subpred RelationalExprBase a
_) RestrictionPredicateExprBase a
acc = forall a.
RestrictionPredicateExprBase a
-> RestrictionPredicateExprBase a -> RestrictionPredicateExprBase a
AndPredicate RestrictionPredicateExprBase a
acc RestrictionPredicateExprBase a
subpred
folder RelationalExprBase a
_ RestrictionPredicateExprBase a
_ = forall a. HasCallStack => [Char] -> a
error [Char]
"unexpected restriction expression in optimization phase"
in
forall a.
RestrictionPredicateExprBase a
-> RelationalExprBase a -> RelationalExprBase a
Restrict GraphRefRestrictionPredicateExpr
andPreds GraphRefRelationalExpr
optFinalExpr
sequentialRestrictions :: RelationalExprBase a -> [RelationalExprBase a]
sequentialRestrictions :: forall a. RelationalExprBase a -> [RelationalExprBase a]
sequentialRestrictions expr :: RelationalExprBase a
expr@(Restrict RestrictionPredicateExprBase a
_ RelationalExprBase a
subexpr) = RelationalExprBase a
exprforall a. a -> [a] -> [a]
:forall a. RelationalExprBase a -> [RelationalExprBase a]
sequentialRestrictions RelationalExprBase a
subexpr
sequentialRestrictions RelationalExprBase a
_ = []
applyStaticRestrictionPushdown :: GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionPushdown :: GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionPushdown GraphRefRelationalExpr
expr = case GraphRefRelationalExpr
expr of
MakeRelationFromExprs Maybe [AttributeExprBase GraphRefTransactionMarker]
_ TupleExprsBase GraphRefTransactionMarker
_ -> GraphRefRelationalExpr
expr
MakeStaticRelation Attributes
_ RelationTupleSet
_ -> GraphRefRelationalExpr
expr
ExistingRelation Relation
_ -> GraphRefRelationalExpr
expr
RelationValuedAttribute{} -> GraphRefRelationalExpr
expr
RelationVariable AttributeName
_ GraphRefTransactionMarker
_ -> GraphRefRelationalExpr
expr
With WithNamesAssocsBase GraphRefTransactionMarker
_ GraphRefRelationalExpr
_ -> GraphRefRelationalExpr
expr
Project AttributeNamesBase GraphRefTransactionMarker
_ GraphRefRelationalExpr
_ -> GraphRefRelationalExpr
expr
Restrict GraphRefRestrictionPredicateExpr
restrictAttrs (Project AttributeNamesBase GraphRefTransactionMarker
projAttrs GraphRefRelationalExpr
subexpr) ->
forall a.
AttributeNamesBase a
-> RelationalExprBase a -> RelationalExprBase a
Project AttributeNamesBase GraphRefTransactionMarker
projAttrs (forall a.
RestrictionPredicateExprBase a
-> RelationalExprBase a -> RelationalExprBase a
Restrict GraphRefRestrictionPredicateExpr
restrictAttrs (GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionPushdown GraphRefRelationalExpr
subexpr))
Restrict GraphRefRestrictionPredicateExpr
restrictAttrs (Union GraphRefRelationalExpr
subexpr1 GraphRefRelationalExpr
subexpr2) ->
let optSub1 :: GraphRefRelationalExpr
optSub1 = GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionPushdown GraphRefRelationalExpr
subexpr1
optSub2 :: GraphRefRelationalExpr
optSub2 = GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionPushdown GraphRefRelationalExpr
subexpr2 in
forall a.
RelationalExprBase a
-> RelationalExprBase a -> RelationalExprBase a
Union (forall a.
RestrictionPredicateExprBase a
-> RelationalExprBase a -> RelationalExprBase a
Restrict GraphRefRestrictionPredicateExpr
restrictAttrs GraphRefRelationalExpr
optSub1) (forall a.
RestrictionPredicateExprBase a
-> RelationalExprBase a -> RelationalExprBase a
Restrict GraphRefRestrictionPredicateExpr
restrictAttrs GraphRefRelationalExpr
optSub2)
Restrict GraphRefRestrictionPredicateExpr
attrs GraphRefRelationalExpr
subexpr ->
forall a.
RestrictionPredicateExprBase a
-> RelationalExprBase a -> RelationalExprBase a
Restrict GraphRefRestrictionPredicateExpr
attrs (GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionPushdown GraphRefRelationalExpr
subexpr)
Union GraphRefRelationalExpr
sub1 GraphRefRelationalExpr
sub2 ->
forall a.
RelationalExprBase a
-> RelationalExprBase a -> RelationalExprBase a
Union (GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionPushdown GraphRefRelationalExpr
sub1) (GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionPushdown GraphRefRelationalExpr
sub2)
Join GraphRefRelationalExpr
sub1 GraphRefRelationalExpr
sub2 ->
forall a.
RelationalExprBase a
-> RelationalExprBase a -> RelationalExprBase a
Join (GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionPushdown GraphRefRelationalExpr
sub1) (GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionPushdown GraphRefRelationalExpr
sub2)
Rename Set (AttributeName, AttributeName)
attrs GraphRefRelationalExpr
sub ->
forall a.
Set (AttributeName, AttributeName)
-> RelationalExprBase a -> RelationalExprBase a
Rename Set (AttributeName, AttributeName)
attrs (GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionPushdown GraphRefRelationalExpr
sub)
Difference GraphRefRelationalExpr
sub1 GraphRefRelationalExpr
sub2 ->
forall a.
RelationalExprBase a
-> RelationalExprBase a -> RelationalExprBase a
Difference (GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionPushdown GraphRefRelationalExpr
sub1) (GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionPushdown GraphRefRelationalExpr
sub2)
Group AttributeNamesBase GraphRefTransactionMarker
n1 AttributeName
n2 GraphRefRelationalExpr
sub ->
forall a.
AttributeNamesBase a
-> AttributeName -> RelationalExprBase a -> RelationalExprBase a
Group AttributeNamesBase GraphRefTransactionMarker
n1 AttributeName
n2 (GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionPushdown GraphRefRelationalExpr
sub)
Ungroup AttributeName
n1 GraphRefRelationalExpr
sub ->
forall a.
AttributeName -> RelationalExprBase a -> RelationalExprBase a
Ungroup AttributeName
n1 (GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionPushdown GraphRefRelationalExpr
sub)
Equals GraphRefRelationalExpr
sub1 GraphRefRelationalExpr
sub2 ->
forall a.
RelationalExprBase a
-> RelationalExprBase a -> RelationalExprBase a
Equals (GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionPushdown GraphRefRelationalExpr
sub1) (GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionPushdown GraphRefRelationalExpr
sub2)
NotEquals GraphRefRelationalExpr
sub1 GraphRefRelationalExpr
sub2 ->
forall a.
RelationalExprBase a
-> RelationalExprBase a -> RelationalExprBase a
NotEquals (GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionPushdown GraphRefRelationalExpr
sub1) (GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionPushdown GraphRefRelationalExpr
sub2)
Extend ExtendTupleExprBase GraphRefTransactionMarker
n GraphRefRelationalExpr
sub ->
forall a.
ExtendTupleExprBase a
-> RelationalExprBase a -> RelationalExprBase a
Extend ExtendTupleExprBase GraphRefTransactionMarker
n (GraphRefRelationalExpr -> GraphRefRelationalExpr
applyStaticRestrictionPushdown GraphRefRelationalExpr
sub)
applyRedundantRenameCleanup :: GraphRefRelationalExpr -> GraphRefRelationalExpr
applyRedundantRenameCleanup :: GraphRefRelationalExpr -> GraphRefRelationalExpr
applyRedundantRenameCleanup = forall t a. Recursive t => (Base t a -> a) -> t -> a
Fold.cata forall {a}.
RelationalExprBaseF a (RelationalExprBase a)
-> RelationalExprBase a
folder
where
folder :: RelationalExprBaseF a (RelationalExprBase a)
-> RelationalExprBase a
folder (RenameF Set (AttributeName, AttributeName)
renameSet RelationalExprBase a
e) =
if forall a. Set a -> Bool
S.null Set (AttributeName, AttributeName)
renameSet then
RelationalExprBase a
e
else
forall a.
Set (AttributeName, AttributeName)
-> RelationalExprBase a -> RelationalExprBase a
Rename (forall a. (a -> Bool) -> Set a -> Set a
S.filter (forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry forall a. Eq a => a -> a -> Bool
(/=)) Set (AttributeName, AttributeName)
renameSet) RelationalExprBase a
e
folder RelationalExprBaseF a (RelationalExprBase a)
e = forall t. Corecursive t => Base t t -> t
Fold.embed RelationalExprBaseF a (RelationalExprBase a)
e
optimizeDatabaseContextIOExpr :: GraphRefDatabaseContextIOExpr -> GraphRefSOptDatabaseContextExprM GraphRefDatabaseContextIOExpr
optimizeDatabaseContextIOExpr :: GraphRefDatabaseContextIOExpr
-> GraphRefSOptDatabaseContextExprM GraphRefDatabaseContextIOExpr
optimizeDatabaseContextIOExpr = forall (f :: * -> *) a. Applicative f => a -> f a
pure